{-# LANGUAGE OverloadedStrings #-}
module Data.CSS.Style.Selector.Specificity(
OrderedRuleStore(..)
) where
import Data.CSS.Syntax.Selector
import Data.CSS.Style.Common
import Data.List
type Vec = (Int, Int, Int)
computeSpecificity :: Text -> Selector -> Vec
computeSpecificity :: Text -> Selector -> Vec
computeSpecificity "" (Element sel :: [SimpleSelector]
sel) = [SimpleSelector] -> Vec
computeSpecificity' [SimpleSelector]
sel
computeSpecificity "" (Child upSel :: Selector
upSel sel :: [SimpleSelector]
sel) = Text -> Selector -> Vec
computeSpecificity "" Selector
upSel Vec -> Vec -> Vec
`add` [SimpleSelector] -> Vec
computeSpecificity' [SimpleSelector]
sel
computeSpecificity "" (Descendant upSel :: Selector
upSel sel :: [SimpleSelector]
sel) = Text -> Selector -> Vec
computeSpecificity "" Selector
upSel Vec -> Vec -> Vec
`add` [SimpleSelector] -> Vec
computeSpecificity' [SimpleSelector]
sel
computeSpecificity "" (Adjacent upSel :: Selector
upSel sel :: [SimpleSelector]
sel) = Text -> Selector -> Vec
computeSpecificity "" Selector
upSel Vec -> Vec -> Vec
`add` [SimpleSelector] -> Vec
computeSpecificity' [SimpleSelector]
sel
computeSpecificity "" (Sibling upSel :: Selector
upSel sel :: [SimpleSelector]
sel) = Text -> Selector -> Vec
computeSpecificity "" Selector
upSel Vec -> Vec -> Vec
`add` [SimpleSelector] -> Vec
computeSpecificity' [SimpleSelector]
sel
computeSpecificity _ sel :: Selector
sel = Text -> Selector -> Vec
computeSpecificity "" Selector
sel Vec -> Vec -> Vec
`add` (0, 0, 1)
computeSpecificity' :: [SimpleSelector] -> Vec
computeSpecificity' :: [SimpleSelector] -> Vec
computeSpecificity' (Namespace _:sel :: [SimpleSelector]
sel) = [SimpleSelector] -> Vec
computeSpecificity' [SimpleSelector]
sel
computeSpecificity' (Tag _:sel :: [SimpleSelector]
sel) = [SimpleSelector] -> Vec
computeSpecificity' [SimpleSelector]
sel Vec -> Vec -> Vec
`add` (0, 0, 1)
computeSpecificity' (Class _:sel :: [SimpleSelector]
sel) = [SimpleSelector] -> Vec
computeSpecificity' [SimpleSelector]
sel Vec -> Vec -> Vec
`add` (0, 1, 0)
computeSpecificity' (Psuedoclass c :: Text
c args :: [Token]
args:sel :: [SimpleSelector]
sel)
| Text
c Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` ["not", "is"], (sels :: [Selector]
sels, []) <- Parser [Selector]
parseSelectors [Token]
args =
[SimpleSelector] -> Vec
computeSpecificity' [SimpleSelector]
sel Vec -> Vec -> Vec
`add` [Vec] -> Vec
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ((Selector -> Vec) -> [Selector] -> [Vec]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Selector -> Vec
computeSpecificity "") [Selector]
sels)
computeSpecificity' (Psuedoclass _ _:sel :: [SimpleSelector]
sel) = [SimpleSelector] -> Vec
computeSpecificity' [SimpleSelector]
sel Vec -> Vec -> Vec
`add` (0, 1, 0)
computeSpecificity' (Property _ _ _:sel :: [SimpleSelector]
sel) = [SimpleSelector] -> Vec
computeSpecificity' [SimpleSelector]
sel Vec -> Vec -> Vec
`add` (0, 1, 0)
computeSpecificity' (Id _:sel :: [SimpleSelector]
sel) = [SimpleSelector] -> Vec
computeSpecificity' [SimpleSelector]
sel Vec -> Vec -> Vec
`add` (1, 0, 0)
computeSpecificity' [] = (0, 0, 0)
add :: Vec -> Vec -> Vec
add :: Vec -> Vec -> Vec
add (a :: Int
a, b :: Int
b, c :: Int
c) (x :: Int
x, y :: Int
y, z :: Int
z) = (Int
a Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
x, Int
b Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
y, Int
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
z)
data OrderedRuleStore inner = OrderedRuleStore inner Int
instance RuleStore inner => RuleStore (OrderedRuleStore inner) where
new :: OrderedRuleStore inner
new = inner -> Int -> OrderedRuleStore inner
forall inner. inner -> Int -> OrderedRuleStore inner
OrderedRuleStore inner
forall a. RuleStore a => a
new 0
addStyleRule :: OrderedRuleStore inner
-> [Int] -> StyleRule' -> OrderedRuleStore inner
addStyleRule (OrderedRuleStore self :: inner
self count :: Int
count) priority :: [Int]
priority rule :: StyleRule'
rule = inner -> Int -> OrderedRuleStore inner
forall inner. inner -> Int -> OrderedRuleStore inner
OrderedRuleStore (
inner -> [Int] -> StyleRule' -> inner
forall a. RuleStore a => a -> [Int] -> StyleRule' -> a
addStyleRule inner
self [Int]
priority (StyleRule' -> inner) -> StyleRule' -> inner
forall a b. (a -> b) -> a -> b
$ StyleRule'
rule {
rank :: ([Int], Vec, Int)
rank = (
[Int]
priority [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ [Int
forall a. Bounded a => a
maxBound],
Text -> Selector -> Vec
computeSpecificity (StyleRule' -> Text
psuedoElement StyleRule'
rule) (Selector -> Vec) -> Selector -> Vec
forall a b. (a -> b) -> a -> b
$ StyleRule' -> Selector
selector StyleRule'
rule,
Int
count)
}
) (Int
count Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 1)
lookupRules :: OrderedRuleStore inner -> Element -> [StyleRule']
lookupRules (OrderedRuleStore self :: inner
self _) el :: Element
el = [StyleRule'] -> [StyleRule']
forall a. Ord a => [a] -> [a]
sort ([StyleRule'] -> [StyleRule']) -> [StyleRule'] -> [StyleRule']
forall a b. (a -> b) -> a -> b
$ inner -> Element -> [StyleRule']
forall a. RuleStore a => a -> Element -> [StyleRule']
lookupRules inner
self Element
el