~alcinnz/haskell-stylist

ref: 8492d01f58f80e2a4b251e9dc38cec99128e8e0d haskell-stylist/src/Stylish/Style/Interpret.hs -rw-r--r-- 3.2 KiB
8492d01f — Adrian Cochrane Implement CSS selector interpretor. 5 years ago
                                                                                
df2761aa Adrian Cochrane
8492d01f Adrian Cochrane
df2761aa Adrian Cochrane
8492d01f Adrian Cochrane
df2761aa Adrian Cochrane
8492d01f Adrian Cochrane
df2761aa Adrian Cochrane
8492d01f Adrian Cochrane
df2761aa Adrian Cochrane
8492d01f Adrian Cochrane
df2761aa Adrian Cochrane
8492d01f Adrian Cochrane
df2761aa Adrian Cochrane
8492d01f Adrian Cochrane
df2761aa Adrian Cochrane
8492d01f Adrian Cochrane
df2761aa Adrian Cochrane
8492d01f 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
{-# LANGUAGE OverloadedStrings #-}
module Stylish.Style.Interpret(
        compile, SelectorFunc(..)
    ) where

import Stylish.Parse.Selector
import Stylish.Element

import Data.Text.Internal (Text(..))
import Data.Text (unpack)
import Data.List
import Data.Maybe

type SelectorFunc = Element -> Bool
type AttrsFunc = [Attribute] -> Bool

compile :: Selector -> SelectorFunc
compile (Element selector) = compileInner selector
compile (Child upSelector selector) = direct parent (compile upSelector) $ compileInner selector
compile (Descendant up sel) = indirect parent (compile up) $ compileInner sel
compile (Adjacent up sel) = direct previous (compile up) $ compileInner sel
compile (Sibling up sel) = indirect previous (compile up) $ compileInner sel

compileInner selector = compileInner' $ lowerInner selector
compileInner' :: (Maybe Text, [(Text, String -> Bool)]) -> SelectorFunc
compileInner' (Just tag, attributes) = testTag tag $ testAttrs (compileAttrs $ sortAttrs attributes) matched
compileInner' (Nothing, attributes) = testAttrs (compileAttrs $ sortAttrs attributes) matched
compileAttrs :: [(Text, String -> Bool)] -> AttrsFunc
compileAttrs ((name, test):attrs) = testAttr name test $ compileAttrs attrs
compileAttrs [] = matched

lowerInner (Tag tag:selector) = (Just tag, snd $ lowerInner selector)
lowerInner (Id id:s) = (tag, ("id", hasWord $ unpack id):tail) where (tag, tail) = lowerInner s
lowerInner (Class c:s) = (tag, ("class", hasWord $ unpack c):tail) where (tag, tail) = lowerInner s
lowerInner (Property name test:s) = (tag, (name, compileAttrTest test):tail)
    where (tag, tail) = lowerInner s
lowerInner [] = (Nothing, [])

compileAttrTest (Equals val) = (== (unpack val))
compileAttrTest (Suffix val) = isSuffixOf $ unpack val
compileAttrTest (Prefix val) = isPrefixOf $ unpack val
compileAttrTest (Substring val) = isInfixOf $ unpack val
compileAttrTest (Include val) = hasWord $ unpack val
compileAttrTest (Dash val) = hasLang $ unpack val

sortAttrs = sortBy compareAttrs where compareAttrs x y = fst x `compare` fst y

--------
---- Runtime
--------
testTag :: Text -> SelectorFunc -> SelectorFunc
testTag tag success el | name el == tag = success el
    | otherwise = False
testAttrs :: AttrsFunc -> SelectorFunc -> SelectorFunc
testAttrs attrsTest success el | attrsTest $ attributes el = success el
    | otherwise = False
direct traverser upTest test el
    | Just parent <- traverser el = test el && upTest parent
    | otherwise = False
indirect :: (Element -> Maybe Element) -> SelectorFunc -> SelectorFunc -> SelectorFunc
indirect traverser upTest test el | Nothing <- traverser el = False
    | not $ test el = False
    | upTest (fromJust $ traverser el) = True
    | otherwise = indirect traverser upTest test $ fromJust $ traverser el
matched _ = True

testAttr :: Text -> (String -> Bool) -> AttrsFunc -> AttrsFunc
testAttr expected test next attrs@(Attribute name value : attrs')
    | name < expected = testAttr expected test next attrs'
    | name > expected = False
    | name == expected && test value = next attrs
    | otherwise = False
testAttr _ _ _ [] = False

hasWord expected value = expected `elem` words value
hasLang _ _ = False -- TODO add support for this.