(.module:
  [library
   [lux {"-" [and]}
    [control
     ["." maybe]]
    [data
     [number
      ["." nat]]
     ["." text
      ["%" format {"+" [format]}]
      ["." encoding {"+" [Encoding]}]]
     [collection
      ["." list ("#\." functor)]]]
    [type
     abstract]
    [world
     [net {"+" [URL]}]]]]
  ["." / "_"
   ["#." selector {"+" [Selector Combinator]}]
   ["#." value {"+" [Value Animation Percentage]}]
   ["#." font {"+" [Font]}]
   ["#." style {"+" [Style]}]
   ["#." query {"+" [Query]}]])

(abstract: .public Common {} Any)
(abstract: .public Special {} Any)

(abstract: .public (CSS brand)
  {}
  
  Text

  (def: .public css
    (-> (CSS Any) Text)
    (|>> :representation))

  (def: .public empty
    (CSS Common)
    (:abstraction ""))

  (def: .public (rule selector style)
    (-> (Selector Any) Style (CSS Common))
    (:abstraction (format (/selector.selector selector) "{" (/style.inline style) "}")))

  (def: .public char_set
    (-> Encoding (CSS Special))
    (|>> encoding.name
         %.text
         (text.enclosed ["@charset " ";"])
         :abstraction))

  (def: .public (font font)
    (-> Font (CSS Special))
    (let [with_unicode (case (value@ #/font.unicode_range font)
                         (#.Some unicode_range)
                         (let [unicode_range' (format "U+" (\ nat.hex encoded (value@ #/font.start unicode_range))
                                                      "-" (\ nat.hex encoded (value@ #/font.end unicode_range)))]
                           (list ["unicode-range" unicode_range']))
                         
                         #.None
                         (list))]
      (|> (list& ["font-family" (value@ #/font.family font)]
                 ["src" (format "url(" (value@ #/font.source font) ")")]
                 ["font-stretch" (|> font (value@ #/font.stretch) (maybe.else /value.normal_stretch) /value.value)]
                 ["font-style" (|> font (value@ #/font.style) (maybe.else /value.normal_style) /value.value)]
                 ["font-weight" (|> font (value@ #/font.weight) (maybe.else /value.normal_weight) /value.value)]
                 with_unicode)
          (list\each (function (_ [property value])
                       (format property ": " value ";")))
          (text.interposed /style.separator)
          (text.enclosed ["{" "}"])
          (format "@font-face")
          :abstraction)))

  (def: .public (import url query)
    (-> URL (Maybe Query) (CSS Special))
    (:abstraction (format (format "@import url(" (%.text url) ")")
                          (case query
                            (#.Some query)
                            (format " " (/query.query query))
                            
                            #.None
                            "")
                          ";")))

  (def: css_separator
    text.new_line)

  (type: .public Frame
    (Record
     [#when Percentage
      #what Style]))

  (def: .public (key_frames animation frames)
    (-> (Value Animation) (List Frame) (CSS Special))
    (:abstraction (format "@keyframes " (/value.value animation) " {"
                          (|> frames
                              (list\each (function (_ frame)
                                           (format (/value.percentage (value@ #when frame)) " {"
                                                   (/style.inline (value@ #what frame))
                                                   "}")))
                              (text.interposed ..css_separator))
                          "}")))

  (template: (!composite <pre> <post>)
    (:abstraction (format (:representation <pre>) ..css_separator
                          (:representation <post>))))
  
  (def: .public (and pre post)
    (-> (CSS Any) (CSS Any) (CSS Any))
    (!composite pre post))

  (def: .public (alter combinator selector css)
    (-> Combinator (Selector Any) (CSS Common) (CSS Common))
    (|> css
        :representation
        (text.all_split_by ..css_separator)
        (list\each (|>> (format (/selector.selector (|> selector (combinator (/selector.tag "")))))))
        (text.interposed ..css_separator)
        :abstraction))

  (def: .public (dependent combinator selector style inner)
    (-> Combinator (Selector Any) Style (CSS Common) (CSS Common))
    (!composite (..rule selector style)
                (..alter combinator selector inner)))

  (template [<name> <combinator>]
    [(def: .public <name>
       (-> (Selector Any) Style (CSS Common) (CSS Common))
       (..dependent <combinator>))]

    [with_descendants /selector.in]
    [with_children /selector.sub]
    )
  )