~alcinnz/haskell-stylist

ref: b8daf07f28d76feec7a0000e1d5c19f6c587f46a haskell-stylist/src/Data/CSS/Style/Cascade.hs -rw-r--r-- 3.0 KiB
b8daf07f — Adrian Cochrane Implement @import & @media 5 years ago
                                                                                
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
{-# LANGUAGE OverloadedStrings #-}
module Data.CSS.Style.Cascade(
        query, cascade,
        TrivialPropertyParser(..), PropertyParser(..), Props
    ) where

import Data.CSS.Style.Common
import Data.CSS.Syntax.Tokens

-- TODO do performance tests to decide beside between strict/lazy,
--      or is another Map implementation better?
import Data.HashMap.Strict
import Data.Text (unpack, pack, isPrefixOf)

class PropertyParser a where
    temp :: a
    inherit :: a -> a
    inherit = id

    shorthand :: a -> Text -> [Token] -> [(Text, [Token])]
    shorthand self key value | Just _ <- longhand self self key value = [(key, value)]
        | otherwise = []
    -- longhand parent self name value
    longhand :: a -> a -> Text -> [Token] -> Maybe a

    getVars :: a -> Props
    getVars _ = []
    setVars :: Props -> a -> a
    setVars _ = id

data TrivialPropertyParser = TrivialPropertyParser (HashMap String [Token])
instance PropertyParser TrivialPropertyParser where
    temp = TrivialPropertyParser empty
    longhand _ (TrivialPropertyParser self) key value =
        Just $ TrivialPropertyParser $ insert (unpack key) value self

type Props = [(Text, [Token])]

--------
---- Query/Psuedo-elements
--------

query :: RuleStore s => s -> Element -> HashMap Text [StyleRule']
query self el = Prelude.foldr yield empty $ lookupRules self el
    where yield rule store = insertWith (++) (psuedoElement rule) [resolveAttr rule el] store

--------
---- Cascade/Inheritance
--------

cascade :: PropertyParser p => [StyleRule'] -> Props -> p -> p
cascade styles overrides base =
    dispatch base (inherit base) $ toList $ cascadeRules (getVars base ++ overrides) styles

cascadeRules :: Props -> [StyleRule'] -> HashMap Text [Token]
cascadeRules overrides rules = cascadeProperties overrides $ concat $ Prelude.map properties rules
cascadeProperties :: Props -> Props -> HashMap Text [Token]
cascadeProperties overrides props = fromList (props ++ overrides)

dispatch, dispatch' :: PropertyParser p => p -> p -> Props -> p
dispatch base child props = dispatch' base (setVars vars child) props
    where vars = Prelude.filter (\(n, _) -> isPrefixOf "--" n) props
dispatch' base child ((key, value):props)
    | Just child' <- longhand base child key value = dispatch base child' props
    | otherwise = dispatch base child props
dispatch' _ child [] = child

--------
---- attr()
--------
resolveAttr :: StyleRule' -> Element -> StyleRule'
resolveAttr self el = self {
        inner = StyleRule sel [(n, resolveAttr' v $ attrs2Dict el) | (n, v) <- attrs] psuedo
    } where StyleRule sel attrs psuedo = inner self

attrs2Dict :: Element -> HashMap Text String
attrs2Dict el = fromList [(a, b) | Attribute a b <- attributes el]

resolveAttr' :: [Token] -> HashMap Text String  -> [Token]
resolveAttr' (Function "attr":Ident attr:RightParen:toks) attrs =
    String (pack $ lookupDefault "" attr attrs) : resolveAttr' toks attrs
resolveAttr' (tok:toks) attrs = tok : resolveAttr' toks attrs
resolveAttr' [] _ = []