(.module: [library [lux (#- and) [data ["." maybe] [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 (get@ #/font.unicode_range font) (#.Some unicode_range) (let [unicode_range' (format "U+" (\ nat.hex encode (get@ #/font.start unicode_range)) "-" (\ nat.hex encode (get@ #/font.end unicode_range)))] (list ["unicode-range" unicode_range'])) #.None (list))] (|> (list& ["font-family" (get@ #/font.family font)] ["src" (format "url(" (get@ #/font.source font) ")")] ["font-stretch" (|> font (get@ #/font.stretch) (maybe.else /value.normal_stretch) /value.value)] ["font-style" (|> font (get@ #/font.style) (maybe.else /value.normal_style) /value.value)] ["font-weight" (|> font (get@ #/font.weight) (maybe.else /value.normal_weight) /value.value)] with_unicode) (list\map (function (_ [property value]) (format property ": " value ";"))) (text.join_with /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 {#when Percentage #what Style}) (def: .public (key_frames animation frames) (-> (Value Animation) (List Frame) (CSS Special)) (:abstraction (format "@keyframes " (/value.value animation) " {" (|> frames (list\map (function (_ frame) (format (/value.percentage (get@ #when frame)) " {" (/style.inline (get@ #what frame)) "}"))) (text.join_with ..css_separator)) "}"))) (template: (!compose
 )
    (:abstraction (format (:representation 
) ..css_separator
                          (:representation ))))
  
  (def: .public (and pre post)
    (-> (CSS Any) (CSS Any) (CSS Any))
    (!compose pre post))

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

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

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

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