~alcinnz/haskell-stylist

ref: 813c306e72e72f1f1620786971e64470643ee323 haskell-stylist/src/Stylish/Style/Selector/Index.hs -rw-r--r-- 3.4 KiB
813c306e — Adrian Cochrane Reorganize modules to make space for styling passes not related to selectors. 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
84
85
86
{-# LANGUAGE OverloadedStrings #-}
module Stylish.Style.Selector.Index (
        StyleIndex(..), styleIndex,
        rulesForElement
    ) where

-- TODO do performance tests to decide beside between strict/lazy.
import Data.HashMap.Strict
import Data.List (nub)
import Stylish.Parse
import Stylish.Element

import Data.Hashable
import Data.Text (unpack, pack)
import Data.Text.Internal (Text(..))

data StyleIndex = StyleIndex {
    indexed :: HashMap SimpleSelector [StyleRule],
    unindexed :: [StyleRule]
}

styleIndex = StyleIndex {indexed = empty, unindexed = []}

lookup' :: SimpleSelector -> HashMap SimpleSelector [a] -> [a]
lookup' = lookupDefault []

instance StyleSheet StyleIndex where
    addRule self (StyleRule _ []) = self
    addRule self rule@(StyleRule selector _) = addRuleForSelector self rule $ simpleSelector selector

simpleSelector (Element s) = s
simpleSelector (Child _ s) = s
simpleSelector (Descendant _ s) = s
simpleSelector (Adjacent _ s) = s
simpleSelector (Sibling _ s) = s

addRuleForSelector self rule [] = self {unindexed = rule : unindexed self}
addRuleForSelector self rule selector = self {
        indexed = insert key (rule : lookup' key index) index
    } where
        key = selectorKey selector
        index = indexed self

selectorKey (tok@(Tag _) : _) = tok
selectorKey (tok@(Id _) : _) = tok
selectorKey (tok@(Class _) : _) = tok
selectorKey (Property prop _ : _) = Property prop Exists

----

rulesForElement :: StyleIndex -> Element -> [StyleRule]
rulesForElement self element = nub $ Prelude.foldr (++) [] rules
    where
        get key = lookup' key index
        index = indexed self
        rules = unindexed self : Prelude.map get (testsForElement element)

testsForElement :: Element -> [SimpleSelector]
testsForElement element =
    (Tag $ name element) : (testsForAttributes $ attributes element)
testsForAttributes (Attribute "class" value:attrs) =
    (Prelude.map (\s -> Class $ pack s) $ words value) ++
        (Property "class" Exists : testsForAttributes attrs)
testsForAttributes (Attribute "id" value:attrs) =
    (Prelude.map (\s -> Id $ pack s) $ words value) ++
        (Property "id" Exists : testsForAttributes attrs)
testsForAttributes (Attribute name _:attrs) =
    Property name Exists : testsForAttributes attrs
testsForAttributes [] = []

-- Implement hashable for SimpleSelector here because it proved challenging to automatically derive it.
instance Hashable SimpleSelector where
    hashWithSalt seed (Tag tag) = seed `hashWithSalt` (0::Int) `hashWithSalt` unpack tag
    hashWithSalt seed (Id id) = seed `hashWithSalt` (1::Int) `hashWithSalt` unpack id
    hashWithSalt seed (Class class_) = seed `hashWithSalt` (2::Int) `hashWithSalt` unpack class_
    hashWithSalt seed (Property prop test) =
        seed `hashWithSalt` (3::Int) `hashWithSalt` unpack prop `hashWithSalt` test

instance Hashable PropertyTest where
    hashWithSalt seed Exists = seed `hashWithSalt` (0::Int)
    hashWithSalt seed (Equals val) = seed `hashWithSalt` (1::Int) `hashWithSalt` unpack val
    hashWithSalt seed (Suffix val) = seed `hashWithSalt` (2::Int) `hashWithSalt` unpack val
    hashWithSalt seed (Prefix val) = seed `hashWithSalt` (3::Int) `hashWithSalt` unpack val
    hashWithSalt seed (Substring val) = seed `hashWithSalt` (4::Int) `hashWithSalt` unpack val
    hashWithSalt seed (Include val) = seed `hashWithSalt` (5::Int) `hashWithSalt` unpack val
    hashWithSalt seed (Dash val) = seed `hashWithSalt` (6::Int) `hashWithSalt` unpack val