| Maintainer | hapytexeu+gh@gmail.com |
|---|---|
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Css3.Selector.Core
Description
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 PseudoElement
- data PseudoSelectorSequence
- (.::) :: SelectorSequence -> PseudoElement -> PseudoSelectorSequence
- data PseudoClass
- = Active
- | Checked
- | Default
- | Disabled
- | Empty
- | Enabled
- | Focus
- | Fullscreen
- | Hover
- | Indeterminate
- | InRange
- | Invalid
- | Lang Language
- | Link
- | NthChild Nth
- | NthLastChild Nth
- | NthLastOfType Nth
- | NthOfType Nth
- | OnlyOfType
- | OnlyChild
- | Optional
- | OutOfRange
- | ReadOnly
- | ReadWrite
- | Required
- | Root
- | Target
- | Valid
- | Visited
- (.:) :: SelectorSequence -> PseudoClass -> SelectorSequence
- pattern FirstChild :: PseudoClass
- pattern FirstOfType :: PseudoClass
- pattern LastChild :: PseudoClass
- pattern LastOfType :: PseudoClass
- type Language = Text
- 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 Negation
- data Nth = Nth {}
- pattern Even :: Nth
- pattern Odd :: Nth
- pattern One :: Nth
- nthValues :: Nth -> [Int]
- nthIsEmpty :: Nth -> Bool
- nthValues0 :: Nth -> [Int]
- nthValues1 :: Nth -> [Int]
- normalizeNth :: Nth -> Nth
- nthContainsValue :: Nth -> Int -> Bool
- data SelectorSpecificity = SelectorSpecificity Int Int Int
- specificity :: ToCssSelector a => a -> Int
- specificityValue :: SelectorSpecificity -> Int
- encode :: Binary a => a -> ByteString
- decode :: Binary a => ByteString -> a
- compressEncode :: (Binary a, ToCssSelector a) => a -> ByteString
- compressEncodeWith :: (Binary a, ToCssSelector a) => CompressParams -> a -> ByteString
- decompressDecode :: (Binary a, ToCssSelector a) => ByteString -> a
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.
Minimal complete definition
Methods
Arguments
| :: 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.
Arguments
| :: 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.
Arguments
| :: 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.
Arguments
| :: 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 |
Arguments
| :: 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 SelectorSequences that
are combined with a SelectorCombinator.
Constructors
| Selector PseudoSelectorSequence | Convert a given |
| Combined PseudoSelectorSequence SelectorCombinator Selector | Create a combined selector where we have a |
Instances
data SelectorCombinator Source #
A type that contains the possible ways to combine SelectorSequences.
Constructors
| 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.
Constructors
| SelectorGroup | |
Fields
| |
Instances
data PseudoElement Source #
An enum type that contains the possible pseudo elements. A pseudo
element is specified by two colon characters (::), followed by the name of
the pseudo element. The After, Before, FirstLine and FirstLetter
can be written with a single colon for backwards compatibility with
CSS 1 and CSS 2.
Constructors
| After | The |
| Before | The |
| FirstLetter | The |
| FirstLine | The |
| Marker | The |
| Placeholder | The |
| Selection | The |
Instances
data PseudoSelectorSequence Source #
A SelectorSequence with an optional PseudoElement at the end. Each element of a Selector can
have at most one PseudoElement.
Constructors
| Sequence SelectorSequence | A data constructor where there is no optional |
| SelectorSequence :.:: PseudoElement | A data constructor for a |
Instances
Arguments
| :: SelectorSequence | The given |
| -> PseudoElement | The given |
| -> PseudoSelectorSequence | The corresponding |
Add a given PseudoElement to the given SelectorSequence to produce a PseudoSelectorSequence. Since
a PseudoElement is an instance of IsString, this can thus be used to combine string literals.
data PseudoClass Source #
A data type that contains the possible pseudo classes. In a CSS selector
the pseudo classes are specified with a single colon, for example :active.
These filter on the state of the items. A full list of pseudo classes
is available here.
Constructors
| Active | The |
| Checked | The |
| Default | The |
| Disabled | The |
| Empty | The |
| Enabled | The |
| Focus | The |
| Fullscreen | The |
| Hover | The |
| Indeterminate | The |
| InRange | The |
| Invalid | The |
| Lang Language | The |
| Link | The |
| NthChild Nth | The |
| NthLastChild Nth | The |
| NthLastOfType Nth | The |
| NthOfType Nth | The |
| OnlyOfType | The |
| OnlyChild | The |
| Optional | The |
| OutOfRange | The |
| ReadOnly | The |
| ReadWrite | The |
| Required | The |
| Root | The |
| Target | The |
| Valid | The |
| Visited | The |
Instances
Arguments
| :: SelectorSequence | The given |
| -> PseudoClass | The given |
| -> SelectorSequence | A |
Filter a given SelectorSequence with a given PseudoClass.
pattern FirstChild :: PseudoClass Source #
A pattern synonym for :nth-child(1). If NthChild (Nth 0 1) is used, then
this will render as :first-child.
pattern FirstOfType :: PseudoClass Source #
A pattern synonym for :nth-of-type(1). If NthOfType (Nth 0 1) is used, then
this will render as :first-of-type.
pattern LastChild :: PseudoClass Source #
A pattern synonym for :nth-last-child(1). If NthLastChild (Nth 0 1) is used, then
this will render as :last-child.
pattern LastOfType :: PseudoClass Source #
A pattern synonym for :nth-last-of-type(1). If NthLastOfType (Nth 0 1) is used, then
this will render as :last-of-type.
data SelectorSequence Source #
A SelectorSequence is a TypeSelector (that can be Universal) followed
by zero, one or more SelectorFilters these filter the selector further, for
example with a Hash, a Class, or an Attrib.
Constructors
| SimpleSelector TypeSelector | Convert a |
| Filter SelectorSequence SelectorFilter | Apply an additional |
Instances
Arguments
| :: 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
Arguments
| :: SelectorCombinator | The |
| -> Selector | The left |
| -> Selector | The right |
| -> Selector | A |
Combines two Selectors with the given SelectorCombinator.
Arguments
| :: Selector | The left |
| -> Selector | The right |
| -> Selector | A selector that is the combination of the left |
Combines two Selectors 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.
Constructors
| SHash Hash | A |
| SClass Class | A |
| SAttrib Attrib | An |
| SPseudo PseudoClass | A |
| SNot Negation | A |
Instances
Arguments
| :: SelectorSequence | The given |
| -> [SelectorFilter] | The given list of |
Obtain the list of filters that are applied in the given
SelectorSequence.
Arguments
| :: SelectorSequence | The given |
| -> [SelectorFilter] | The given list of |
Obtain the list of filters that are applied in the given SelectorSequence
in reversed order.
Arguments
| :: SelectorSequence | The |
| -> [SelectorFilter] | The list of |
| -> SelectorSequence | A modified |
Add a given list of SelectorFilters to the given SelectorSequence. The
filters are applied left-to-right.
Arguments
| :: 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).
Constructors
| 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.
Constructors
| 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.
Constructors
| TypeSelector | |
Fields
| |
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.
Arguments
| :: 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.).
Constructors
| 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.
Constructors
| 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.
Constructors
| AttributeName | |
Fields
| |
Instances
type AttributeValue = Text Source #
We use Text as the type to store an attribute value.
Arguments
| :: 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.
Arguments
| :: 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.
Arguments
| :: 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.
Arguments
| :: 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.
Arguments
| :: 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.
Arguments
| :: 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.
Arguments
| :: 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 #
Arguments
| :: 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
| Arbitrary Class Source # | |
| Data Class Source # | |
Defined in Css3.Selector.Core Methods 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 :: forall r r'. (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 # | |
| IsString Class Source # | |
Defined in Css3.Selector.Core Methods fromString :: String -> Class # | |
| Generic Class Source # | |
| Show Class Source # | |
| Binary Class Source # | |
| ToCssSelector Class Source # | |
Defined in Css3.Selector.Core Methods toCssSelector :: Class -> Text Source # toSelectorGroup :: Class -> SelectorGroup Source # specificity' :: Class -> SelectorSpecificity Source # | |
| NFData Class Source # | |
Defined in Css3.Selector.Core | |
| Eq Class Source # | |
| Ord Class Source # | |
| Hashable Class Source # | |
Defined in Css3.Selector.Core | |
| type Rep Class Source # | |
Defined in Css3.Selector.Core | |
Arguments
| :: 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
| Arbitrary Hash Source # | |
| Data Hash Source # | |
Defined in Css3.Selector.Core Methods 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 :: forall r r'. (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 # | |
| IsString Hash Source # | |
Defined in Css3.Selector.Core Methods fromString :: String -> Hash # | |
| Generic Hash Source # | |
| Show Hash Source # | |
| Binary Hash Source # | |
| ToCssSelector Hash Source # | |
Defined in Css3.Selector.Core Methods toCssSelector :: Hash -> Text Source # toSelectorGroup :: Hash -> SelectorGroup Source # specificity' :: Hash -> SelectorSpecificity Source # | |
| NFData Hash Source # | |
Defined in Css3.Selector.Core | |
| Eq Hash Source # | |
| Ord Hash Source # | |
| Hashable Hash Source # | |
Defined in Css3.Selector.Core | |
| type Rep Hash Source # | |
Defined in Css3.Selector.Core | |
Arguments
| :: SelectorSequence | The given |
| -> Hash | The given |
| -> SelectorSequence | A |
Filter a given SelectorSequence with a given Hash.
Negation
A data type that contains all possible items that can be used in a :not(…) clause.
Since a :not(…) cannot be nested in another :not(…), we see an SNot as a special
case, and not as a PseudoClass.
Constructors
| NTypeSelector TypeSelector | A |
| NHash Hash | A |
| NClass Class | A |
| NAttrib Attrib | An |
| NPseudo PseudoClass | A |
| NPseudoElement PseudoElement | A |
Instances
Nth items
A data type that is used to select children and elements of type with the :nth-child, :nth-last-child, :nth-last-of-type and :nth-of-type.
if the One is used as argument, then the pseudo classes are :first-child, :first-of-type, :last-child, and :last-of-type.
Constructors
| Nth | |
Instances
| Arbitrary Nth Source # | |
| Data Nth Source # | |
Defined in Css3.Selector.Core Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Nth -> c Nth # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Nth # dataTypeOf :: Nth -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Nth) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Nth) # gmapT :: (forall b. Data b => b -> b) -> Nth -> Nth # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Nth -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Nth -> r # gmapQ :: (forall d. Data d => d -> u) -> Nth -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Nth -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Nth -> m Nth # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Nth -> m Nth # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Nth -> m Nth # | |
| Generic Nth Source # | |
| Read Nth Source # | |
| Show Nth Source # | |
| Binary Nth Source # | |
| Default Nth Source # | The default of the Nth instance is |
Defined in Css3.Selector.Core | |
| NFData Nth Source # | |
Defined in Css3.Selector.Core | |
| Eq Nth Source # | |
| Ord Nth Source # | |
| Hashable Nth Source # | |
Defined in Css3.Selector.Core | |
| Lift Nth Source # | |
| IsString (Nth -> PseudoClass) Source # | |
Defined in Css3.Selector.Core Methods fromString :: String -> Nth -> PseudoClass # | |
| type Rep Nth Source # | |
Defined in Css3.Selector.Core type Rep Nth = D1 ('MetaData "Nth" "Css3.Selector.Core" "css-selectors-0.5.0.0-IRHvBYIUFt2F9g7LJtpxg2" 'False) (C1 ('MetaCons "Nth" 'PrefixI 'True) (S1 ('MetaSel ('Just "linear") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "constant") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) | |
A pattern synonym that is used in CSS to specify a sequence that starts with two and each time increases with two.
A pattern synonym that is used in CSS to specify a sequence that starts with one and each time increases with two.
An Nth item that spans a collection with only 1 as value. This is used to transform :nth-child to :first-child for example.
Arguments
| :: Nth | |
| -> [Int] | A list of one-based indexes that contain the items selected by the |
Obtain the one-based indices that match the given Nth object. The CSS3 selectors
are one-based: the first child has index 1.
Arguments
| :: Nth | The given |
| -> Bool |
|
Check if the given Nth object contains no items.
Arguments
| :: Nth | |
| -> [Int] | A list of zero-based indexes that contain the items selected by the |
Obtain the zero-based indices that match the given Nth object. One can use this for list/vector processing since
the CSS3 selectors start with index 1. The nthValues1 can be used for one-based indexes.
Arguments
| :: Nth | The given |
| -> Nth | The normalized variant of the given |
Normalize the given Nth object to a normalized one. If and only if the
normalized variants are the same of two Nth objects, then these will produce
the same list of values. Normalization is idempotent: calling normalizeNth
on a normalized Nth will produce the same Nth.
Arguments
| :: Nth | The given |
| -> Int | The given index for which we check if it is contained in the given |
| -> Bool | This function returns |
Check if the given Nth object contains a given value.
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.
Constructors
| SelectorSpecificity Int Int Int | Create a |
Instances
Arguments
| :: 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.
Arguments
| :: SelectorSpecificity | The |
| -> Int | The specificity level of the |
Calculate the specificity value of the SelectorSpecificity
Read and write binary content
encode :: Binary a => a -> ByteString #
Encode a value using binary serialisation to a lazy ByteString.
decode :: Binary a => ByteString -> a #
Decode a value from a lazy ByteString, reconstructing the original structure.
Arguments
| :: (Binary a, ToCssSelector a) | |
| => a | The object to turn into a compressed |
| -> ByteString | A compressed binary representation of the given object. |
Convert the given item to a compressed ByteString. This can be used to write to and read from a file for example.
The econding format is not an official format: it is constructed based on the structure of the Haskell types. That
stream is then passed through a gzip implementation.
Arguments
| :: (Binary a, ToCssSelector a) | |
| => CompressParams | The parameters that determine how to compress the |
| -> a | The object to turn into a compressed |
| -> ByteString | A compressed binary representation of the given object. |
Convert the given item to a compressed ByteString. This can be used to write to and read from a file for example.
The econding format is not an official format: it is constructed based on the structure of the Haskell types. That
stream is then passed through a gzip implementation.
Arguments
| :: (Binary a, ToCssSelector a) | |
| => ByteString | A compressed binary representation of a |
| -> a | The corresponding decompressed and decoded logic. |
Convert the given item to a compressed ByteString. This can be used to write to and read from a file for example.
The econding format is not an official format: it is constructed based on the structure of the Haskell types. That
stream is then passed through a gzip implementation.