~alcinnz/haskell-stylist

ref: 8ffc0dd2a20595c45184c1a2573e80f97bcd9f8e haskell-stylist/src/Data/CSS/Preprocessor/Text.hs -rw-r--r-- 6.0 KiB
8ffc0dd2 — Adrian Cochrane Implement CSS3 counters. 4 years ago
                                                                                
9e14bcfe Adrian Cochrane
8ffc0dd2 Adrian Cochrane
9e14bcfe Adrian Cochrane
8ffc0dd2 Adrian Cochrane
9e14bcfe Adrian Cochrane
8ffc0dd2 Adrian Cochrane
9e14bcfe Adrian Cochrane
8ffc0dd2 Adrian Cochrane
9e14bcfe Adrian Cochrane
8ffc0dd2 Adrian Cochrane
9e14bcfe Adrian Cochrane
8ffc0dd2 Adrian Cochrane
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
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
{-# LANGUAGE OverloadedStrings #-}
-- | Lowers certain CSS properties to plain text.
module Data.CSS.Preprocessor.Text(TextStyle, resolve, StyleTree(..)) where

import Data.CSS.Syntax.Tokens (Token(..), NumericValue(..))
import Data.CSS.Style (PropertyParser(..))
import Data.CSS.StyleTree
import qualified Data.Text as Txt
import Data.Text (Text)

import Data.Maybe (fromMaybe)
import qualified Data.HashMap.Lazy as M
import Data.Function ((&))

type Counters = [(Text, Integer)]
-- | `PropertyParser` decorator that parses & lowers certain CSS properties to plain text.
data TextStyle p = TextStyle {
    inner :: p,
    content :: [Token],

    counterReset :: Counters,
    counterIncrement :: Counters,
    counterSet :: Counters
}

instance PropertyParser p => PropertyParser (TextStyle p) where
    temp = TextStyle {
            inner = temp,
            content = [],
            counterReset = [],
            counterIncrement = [],
            counterSet = []
        }
    inherit parent = TextStyle {
            inner = inherit $ inner parent,
            content = [],
            counterReset = [],
            counterIncrement = [],
            counterSet = []
        }

    shorthand self "content" value = shorthand (inner self) "content" $ removeCounters value
    shorthand _ key value
        | key `elem` ["counter-reset", "counter-increment", "counter-set"],
            Just _ <- parseCounters 0 value = [(key, value)]
    shorthand self key value = shorthand (inner self) key value

    longhand _ self "content" value = Just $ self {content = value}
    longhand _ self "counter-reset" value = (\v -> self {counterReset = v}) <$> parseCounters 0 value
    longhand _ self "counter-increment" value = (\v -> self {counterIncrement = v}) <$> parseCounters 1 value
    longhand _ self "counter-set" value = (\v -> self {counterSet = v}) <$> parseCounters 0 value
    longhand parent self key value = (\v -> self {inner = v}) <$> longhand (inner parent ) (inner self) key value

removeCounters :: [Token] -> [Token]
removeCounters (Function "counter":Ident _:RightParen:toks) = String "" : removeCounters toks
removeCounters (Function "counters":Ident _:Comma:String _:toks) = String "" : removeCounters toks
removeCounters (tok:toks) = tok : removeCounters toks
removeCounters [] = []

parseCounters :: Integer -> [Token] -> Maybe [(Text, Integer)]
parseCounters _ [Ident "none"] = Just []
parseCounters _ [] = Just []
parseCounters x (Ident counter : Number _ (NVInteger count') : toks) =
    (:) (counter, count') <$> parseCounters x toks
parseCounters x (Ident counter : toks) = (:) (counter, x) <$> parseCounters x toks
parseCounters _ _ = Nothing

resolve :: PropertyParser p => StyleTree (TextStyle p) -> StyleTree p
resolve = applyCounters

--------
---- Counters
--------
type Context = M.HashMap Text [([Integer], Integer)]

inheritCounters :: Context -> Context -> Context
inheritCounters counterSource valueSource = M.intersectionWith cb valueSource counterSource -- indexed by name & el-path
    where cb val source = [counter | counter@(path, _) <- val, path `elem` [p | (p, _) <- source]]

instantiateCounter :: Context -> Path -> Text -> Integer -> Context
instantiateCounter counters path name val = M.insertWith appendCounter name [(path, val)] counters
    where
        appendCounter new (old@((_:oldPath), _):olds)
            | oldPath == tail path = new ++ olds
            | otherwise =  new ++ (old:olds)
        appendCounter new [] = new
        appendCounter new (_:olds) = new ++ olds
instantiateCounters :: Path -> Counters -> Context -> Context
instantiateCounters path instruct counters = foldl cb counters instruct
    where cb counters' (name, value) = instantiateCounter counters' path name value

incrementCounter :: Context -> Path -> Text -> Integer -> Context
incrementCounter counters path name val = M.insertWith addCounter name [(path, val)] counters
    where
        addCounter ((_, new):_) ((path', old):rest) = (path', new + old):rest
        addCounter [] old = old
        addCounter new [] = new
incrementCounters :: Path -> Counters -> Context -> Context
incrementCounters path instruct counters = foldl cb counters instruct
    where cb counters' (name, value) = incrementCounter counters' path name value

setCounter :: Context -> Path -> Text -> Integer -> Context
setCounter counters path name val = M.insertWith setCounter' name [(path, val)] counters
    where
        setCounter' ((_, val'):_) ((path', _):rest) = (path', val'):rest
        setCounter' [] old = old
        setCounter' new [] = new
setCounters :: Path -> Counters -> Context -> Context
setCounters path instruct counters = foldl cb counters instruct
    where cb counters' (name, value) = setCounter counters' path name value


renderCounters :: Context -> [Token] -> [Token]
renderCounters counters (Function "counter":Ident name:RightParen:toks)
    | Just ((_, count):_) <- name `M.lookup` counters =
        String (Txt.pack $ show count) : renderCounters counters toks
    | otherwise = renderCounters counters toks
renderCounters counters (Function "counters":Ident name:Comma:String sep:RightParen:toks)
    | Just counter <- name `M.lookup` counters = String (Txt.intercalate sep [
        Txt.pack $ show count | (_, count) <- reverse counter
    ]) : renderCounters counters toks
    | otherwise = renderCounters counters toks
renderCounters counters (tok:toks) = tok : renderCounters counters toks
renderCounters _ [] = []

applyCounters :: PropertyParser p => StyleTree (TextStyle p) -> StyleTree p
applyCounters = treeOrder applyCounters0 M.empty
applyCounters0 :: PropertyParser p => Context -> Context -> Path -> TextStyle p -> (Context, p)
applyCounters0 counterSource valueSource path node =
    let counters = inheritCounters counterSource valueSource &
            instantiateCounters path (counterReset node) &
            incrementCounters path (counterIncrement node) &
            setCounters path (counterSet node)
    in let inner' = inner node
    in (counters,
        fromMaybe inner' $ longhand temp inner' "content" $ renderCounters counters $ content node)