module Text.XML.HXT.CSS.TypeDefs where
import Data.Char
newtype SelectorsGroup = SelectorsGroup [Selector]
deriving (Show, Eq)
data Selector
= Selector SimpleSelectorSeq
| Descendant SimpleSelectorSeq Selector
| Child SimpleSelectorSeq Selector
| AdjSibling SimpleSelectorSeq Selector
| FolSibling SimpleSelectorSeq Selector
deriving (Show, Eq)
newtype SimpleSelectorSeq =
SimpleSelectorSeq [SimpleSelector]
deriving (Show, Eq)
data SimpleSelector
= UniversalSelector
| TypeSelector String
| IdSelector String
| ClassSelector String
| AttrSelector String AttrTest
| Pseudo PseudoClass
| PseudoNth PseudoNthClass
| Negation SimpleSelector
deriving (Show, Eq)
data AttrTest
= AttrExists
| AttrEq String
| AttrContainsSp String
| AttrBeginHy String
| AttrPrefix String
| AttrSuffix String
| AttrSubstr String
deriving (Show, Eq)
data PseudoClass
= PseudoFirstChild
| PseudoLastChild
| PseudoOnlyChild
| PseudoFirstOfType
| PseudoLastOfType
| PseudoOnlyOfType
| PseudoEmpty
| PseudoRoot
deriving (Show, Eq)
data PseudoNthClass
= PseudoNthChild Nth
| PseudoNthLastChild Nth
| PseudoNthOfType Nth
| PseudoNthLastOfType Nth
deriving (Show, Eq)
data Nth
= Nth Int Int
| Odd
| Even
deriving (Show, Eq)
findPseudoClass :: String -> Maybe PseudoClass
findPseudoClass = flip lookup h . map toLower
where
h = [ ("first-child", PseudoFirstChild)
, ("last-child", PseudoLastChild)
, ("only-child", PseudoOnlyChild)
, ("first-of-type", PseudoFirstOfType)
, ("last-of-type", PseudoLastOfType)
, ("only-of-type", PseudoOnlyOfType)
, ("empty", PseudoEmpty)
, ("root", PseudoRoot)
]
findPseudoNthClass :: String -> Maybe (Nth -> PseudoNthClass)
findPseudoNthClass = flip lookup h . map toLower
where
h = [ ("nth-child", PseudoNthChild)
, ("nth-last-child", PseudoNthLastChild)
, ("nth-of-type", PseudoNthOfType)
, ("nth-last-of-type", PseudoNthLastOfType)
]
testNth :: Nth -> Int -> Bool
testNth (Nth 0 b) k = k == b
testNth (Nth a b) k = r == 0 && n >= 0
where
(n, r) = (k b) `quotRem` a
testNth Odd k = odd k
testNth Even k = even k