Maintainer | hapytexeu+gh@gmail.com |
---|---|
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
A module that defines the tree of types to represent and manipulate a css selector. These data types are members of several typeclasses to make these more useful.
Synopsis
- class ToCssSelector a where
- toCssSelector :: a -> Text
- toSelectorGroup :: a -> SelectorGroup
- specificity' :: a -> SelectorSpecificity
- toPattern :: a -> Pat
- normalize :: a -> a
- data Selector
- data SelectorCombinator
- newtype SelectorGroup = SelectorGroup {}
- data SelectorSequence
- combinatorText :: SelectorCombinator -> Text
- combine :: SelectorCombinator -> Selector -> Selector -> Selector
- (.>) :: Selector -> Selector -> Selector
- (.+) :: Selector -> Selector -> Selector
- (.~) :: Selector -> Selector -> Selector
- data SelectorFilter
- filters :: SelectorSequence -> [SelectorFilter]
- filters' :: SelectorSequence -> [SelectorFilter]
- addFilters :: SelectorSequence -> [SelectorFilter] -> SelectorSequence
- (.:) :: SelectorSequence -> [SelectorFilter] -> SelectorSequence
- data Namespace
- pattern NEmpty :: Namespace
- data ElementName
- = EAny
- | ElementName Text
- data TypeSelector = TypeSelector {}
- pattern Universal :: TypeSelector
- (.|) :: Namespace -> ElementName -> TypeSelector
- data Attrib
- data AttributeCombinator
- data AttributeName = AttributeName {}
- type AttributeValue = Text
- (.=) :: AttributeName -> AttributeValue -> Attrib
- (.~=) :: AttributeName -> AttributeValue -> Attrib
- (.|=) :: AttributeName -> AttributeValue -> Attrib
- (.^=) :: AttributeName -> AttributeValue -> Attrib
- (.$=) :: AttributeName -> AttributeValue -> Attrib
- (.*=) :: AttributeName -> AttributeValue -> Attrib
- attrib :: AttributeCombinator -> AttributeName -> AttributeValue -> Attrib
- attributeCombinatorText :: AttributeCombinator -> AttributeValue
- newtype Class = Class {}
- (...) :: SelectorSequence -> Class -> SelectorSequence
- newtype Hash = Hash {}
- (.#) :: SelectorSequence -> Hash -> SelectorSequence
- data SelectorSpecificity = SelectorSpecificity Int Int Int
- specificity :: ToCssSelector a => a -> Int
- specificityValue :: SelectorSpecificity -> Int
ToCssSelector typeclass
class ToCssSelector a where Source #
A class that defines that the given type can be converted to a css selector value, and has a certain specificity.
:: a | The given object for which we calculate the css selector. |
-> Text | The css selector text for the given object. |
Convert the given element to a Text
object that contains the css
selector.
:: a | The item to lift to a |
-> SelectorGroup | The value of a |
Lift the given ToCssSelector
type object to a SelectorGroup
, which
is the "root type" of the css selector hierarchy.
:: a | The item for which we calculate the specificity level. |
-> SelectorSpecificity | The specificity level of the given item.
Convert the given |
Calculate the specificity of the css selector by returing a
SelectorSpecificity
object.
:: a | The item to convert to a |
-> Pat | The pattern that is generated that will match only items equal to the given object.
Convert the given |
:: a | The item to normalize. |
-> a | A normalized variant of the given item. This will filter the same objects, and have the same specificity. |
Instances
Selectors and combinators
The type of a single selector. This is a sequence of SelectorSequence
s that
are combined with a SelectorCombinator
.
Selector SelectorSequence | Convert a given |
Combined SelectorSequence SelectorCombinator Selector | Create a combined selector where we have a |
Instances
data SelectorCombinator Source #
A type that contains the possible ways to combine SelectorSequence
s.
Descendant | The second tag is a descendant of the first one, denoted in css with a space. |
Child | The second tag is the (direct) child of the first one, denoted with a |
DirectlyPreceded | The second tag is directly preceded by the first one, denoted with a |
Preceded | The second tag is preceded by the first one, denoted with a |
Instances
newtype SelectorGroup Source #
The root type of a css selector. This is a comma-separated list of selectors.
SelectorGroup | |
|
Instances
data SelectorSequence Source #
A SelectorSequence
is a TypeSelector
(that can be Universal
) followed
by zero, one or more SelectorFilter
s these filter the selector further, for
example with a Hash
, a Class
, or an Attrib
.
SimpleSelector TypeSelector | Convert a |
Filter SelectorSequence SelectorFilter | Apply an additional |
Instances
:: SelectorCombinator | The given |
-> Text | The css selector token that is used for the given |
Convert the SelectorCombinator
to the equivalent css selector text. A
space for Descendant
, a >
for Child
, a +
for DirectlyPreceded
, and
a ~
for Preceded
:: SelectorCombinator | The |
-> Selector | The left |
-> Selector | The right |
-> Selector | A |
Combines two Selector
s with the given SelectorCombinator
.
:: Selector | The left |
-> Selector | The right |
-> Selector | A selector that is the combination of the left |
Combines two Selector
s with the DirectlyPreceded
combinator.
Filters
data SelectorFilter Source #
A type that sums up the different ways to filter a type selector: with an id (hash), a class, and an attribute.
SHash Hash | A |
SClass Class | A |
SAttrib Attrib | An |
Instances
:: SelectorSequence | The given |
-> [SelectorFilter] | The given list of |
Obtain the list of filters that are applied in the given
SelectorSequence
.
:: SelectorSequence | The given |
-> [SelectorFilter] | The given list of |
Obtain the list of filters that are applied in the given SelectorSequence
in reversed order.
:: SelectorSequence | The |
-> [SelectorFilter] | The list of |
-> SelectorSequence | A modified |
Add a given list of SelectorFilter
s to the given SelectorSequence
. The
filters are applied left-to-right.
:: SelectorSequence | The |
-> [SelectorFilter] | The list of |
-> SelectorSequence | A modified |
An infix variant of the addFilters
function.
Namespaces
The namespace of a css selector tag. The namespace can be NAny
(all
possible namespaces), or a namespace with a given text (this text can be
empty).
NAny | A typeselector part that specifies that we accept all namespaces, in css denoted with |
Namespace Text | A typselector part that specifies that we accept a certain namespace name. |
Instances
pattern NEmpty :: Namespace Source #
The empty namespace. This is not the wildcard namespace (*
). This is a
bidirectional namespace and can thus be used in expressions as well.
Type selectors
data ElementName Source #
The element name of a css selector tag. The element name can be EAny
(all
possible tag names), or an element name with a given text.
EAny | A typeselector part that specifies that we accept all element names, in css denoted with |
ElementName Text | A typeselector part that specifies that we accept a certain element name. |
Instances
data TypeSelector Source #
A typeselector is a combination of a selector for a namespace, and a selector for an element name. One, or both can be a wildcard.
TypeSelector | |
|
Instances
pattern Universal :: TypeSelector Source #
The universal type selector: a selector that matches all types in all namespaces (including the empty namespace). This pattern is bidirectional and thus can be used in expressions as well.
:: Namespace | The |
-> ElementName | The |
-> TypeSelector | A |
Construct a TypeSelector
with a given Namespace
and ElementName
.
Attributes
A css attribute can come in two flavors: either a constraint that the attribute should exists, or a constraint that a certain attribute should have a certain value (prefix, suffix, etc.).
Exist AttributeName | A constraint that the given |
Attrib AttributeName AttributeCombinator AttributeValue | A constraint about the value associated with the given |
Instances
data AttributeCombinator Source #
The possible ways to match an attribute with a given value in a css selector.
Exact | The attribute has exactly the value of the value, denoted with |
Include | The attribute has a whitespace separated list of items, one of these items is the value, denoted with |
DashMatch | The attribute has a hyphen separated list of items, the first item is the value, denoted with |
PrefixMatch | The value is a prefix of the value in the attribute, denoted with |
SuffixMatch | The value is a suffix of the value in the attribute, denoted with |
SubstringMatch | The value is a substring of the value in the attribute, denoted with |
Instances
data AttributeName Source #
An attribute name is a name that optionally has a namespace, and the name of the attribute.
AttributeName | |
|
Instances
type AttributeValue = Text Source #
We use Text
as the type to store an attribute value.
:: AttributeName | The name of the attribute to constraint. |
-> AttributeValue | The value that constraints the attribute. |
-> Attrib | The |
Create an Attrib
where the given AttributeName
is constrainted to be
exactly the given value.
:: AttributeName | The name of the attribute to constraint. |
-> AttributeValue | The value that constraints the attribute. |
-> Attrib | The |
Create an Attrib
where the given AttributeName
is constrainted such
that the attribute is a whitespace seperated list of items, and the value is
one of these items.
:: AttributeName | The name of the attribute to constraint. |
-> AttributeValue | The value that constraints the attribute. |
-> Attrib | The |
Create an Attrib
where the given AttributeName
is constrainted such
that the attribute is a dash seperated list of items, and the value is
the first of these items.
:: AttributeName | The name of the attribute to constraint. |
-> AttributeValue | The value that constraints the attribute. |
-> Attrib | The |
Create an Attrib
where the given AttributeName
is constrainted such
that the attribute has as prefix the given AttributeValue
.
:: AttributeName | The name of the attribute to constraint. |
-> AttributeValue | The value that constraints the attribute. |
-> Attrib | The |
Create an Attrib
where the given AttributeName
is constrainted such
that the attribute has as suffix the given AttributeValue
.
:: AttributeName | The name of the attribute to constraint. |
-> AttributeValue | The value that constraints the attribute. |
-> Attrib | The |
Create an Attrib
where the given AttributeName
is constrainted such
that the attribute has as substring the given AttributeValue
.
:: AttributeCombinator | The |
-> AttributeName | The name of an attribute to filter. |
-> AttributeValue | The value of the attribute to filter. |
-> Attrib | The result is an |
A flipped version of the Attrib
data constructor, where one first
specifies the conbinator, then the AttributeName
and finally the value.
attributeCombinatorText Source #
:: AttributeCombinator | The |
-> AttributeValue | The css selector text for the given |
Convert the given AttributeCombinator
to its css selector counterpart.
Classes
A css class, this is wrapped in a data type. The type only wraps the class name, not the dot prefix.
Instances
Eq Class Source # | |
Data Class Source # | |
Defined in Css.Selector.Core gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Class -> c Class # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Class # dataTypeOf :: Class -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Class) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Class) # gmapT :: (forall b. Data b => b -> b) -> Class -> Class # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Class -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Class -> r # gmapQ :: (forall d. Data d => d -> u) -> Class -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Class -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Class -> m Class # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Class -> m Class # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Class -> m Class # | |
Ord Class Source # | |
Show Class Source # | |
IsString Class Source # | |
Defined in Css.Selector.Core fromString :: String -> Class # | |
Arbitrary Class Source # | |
ToCssSelector Class Source # | |
Defined in Css.Selector.Core toCssSelector :: Class -> Text Source # toSelectorGroup :: Class -> SelectorGroup Source # specificity' :: Class -> SelectorSpecificity Source # |
:: SelectorSequence | The given 'SelectorSequence to filter. |
-> Class | The given |
-> SelectorSequence | A |
Filter a given SelectorSequence
with a given Class
.
Hashes
A css hash (used to match an element with a given id). The type only wraps
the hash name, not the hash (#
) prefix.
Instances
Eq Hash Source # | |
Data Hash Source # | |
Defined in Css.Selector.Core gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Hash -> c Hash # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Hash # dataTypeOf :: Hash -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Hash) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Hash) # gmapT :: (forall b. Data b => b -> b) -> Hash -> Hash # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Hash -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Hash -> r # gmapQ :: (forall d. Data d => d -> u) -> Hash -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Hash -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Hash -> m Hash # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Hash -> m Hash # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Hash -> m Hash # | |
Ord Hash Source # | |
Show Hash Source # | |
IsString Hash Source # | |
Defined in Css.Selector.Core fromString :: String -> Hash # | |
Arbitrary Hash Source # | |
ToCssSelector Hash Source # | |
Defined in Css.Selector.Core toCssSelector :: Hash -> Text Source # toSelectorGroup :: Hash -> SelectorGroup Source # specificity' :: Hash -> SelectorSpecificity Source # |
:: SelectorSequence | The given |
-> Hash | The given |
-> SelectorSequence | A |
Filter a given SelectorSequence
with a given Hash
.
Specificity
data SelectorSpecificity Source #
A datastructure that specifies the selectivity of a css selector. The
specificity is calculated based on three integers: a
, b
and c
.
The specificity is calculated with 100*a+10*b+c
where a
, b
and c
count certain elements of the css selector.
SelectorSpecificity Int Int Int | Create a |
Instances
:: ToCssSelector a | |
=> a | The object for which we evaluate the specificity. |
-> Int | The specificity level as an |
Calculate the specificity of a ToCssSelector
type object. This is done by
calculating the SelectorSpecificity
object, and then calculating the value
of that object.
:: SelectorSpecificity | The |
-> Int | The specificity level of the |
Calculate the specificity value of the SelectorSpecificity