css-selectors-0.4.0.3: Parsing, rendering and manipulating css selectors in Haskell.
Maintainerhapytexeu+gh@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

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

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

toCssSelector, toSelectorGroup, specificity', toPattern

Methods

toCssSelector Source #

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.

toSelectorGroup Source #

Arguments

:: a

The item to lift to a SelectorGroup

-> SelectorGroup

The value of a SelectorGroup of which the object is the selective part.

Lift the given ToCssSelector type object to a SelectorGroup, which is the "root type" of the css selector hierarchy.

specificity' Source #

Arguments

:: a

The item for which we calculate the specificity level.

-> SelectorSpecificity

The specificity level of the given item. Convert the given ToCssSelector item to a Pat pattern, such that we can use it in functions.

Calculate the specificity of the css selector by returing a SelectorSpecificity object.

toPattern Source #

Arguments

:: a

The item to convert to a Pat.

-> Pat

The pattern that is generated that will match only items equal to the given object. Convert the given ToCssSelector item to an item in a more normalized form. A normalization is idempotent: applying this multiple times will have the same effect as applying it once.

normalize Source #

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

Instances details
ToCssSelector Hash Source # 
Instance details

Defined in Css3.Selector.Core

ToCssSelector Class Source # 
Instance details

Defined in Css3.Selector.Core

ToCssSelector AttributeName Source # 
Instance details

Defined in Css3.Selector.Core

ToCssSelector TypeSelector Source # 
Instance details

Defined in Css3.Selector.Core

ToCssSelector ElementName Source # 
Instance details

Defined in Css3.Selector.Core

ToCssSelector Namespace Source # 
Instance details

Defined in Css3.Selector.Core

ToCssSelector Attrib Source # 
Instance details

Defined in Css3.Selector.Core

ToCssSelector SelectorFilter Source # 
Instance details

Defined in Css3.Selector.Core

ToCssSelector SelectorSequence Source # 
Instance details

Defined in Css3.Selector.Core

ToCssSelector Selector Source # 
Instance details

Defined in Css3.Selector.Core

ToCssSelector SelectorGroup Source # 
Instance details

Defined in Css3.Selector.Core

Selectors and combinators

data Selector Source #

The type of a single selector. This is a sequence of SelectorSequences that are combined with a SelectorCombinator.

Constructors

Selector SelectorSequence

Convert a given SelectorSequence to a Selector.

Combined SelectorSequence SelectorCombinator Selector

Create a combined selector where we have a SelectorSequence that is combined with a given SelectorCombinator to a Selector.

Instances

Instances details
Eq Selector Source # 
Instance details

Defined in Css3.Selector.Core

Data Selector Source # 
Instance details

Defined in Css3.Selector.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Selector -> c Selector #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Selector #

toConstr :: Selector -> Constr #

dataTypeOf :: Selector -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Selector) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Selector) #

gmapT :: (forall b. Data b => b -> b) -> Selector -> Selector #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Selector -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Selector -> r #

gmapQ :: (forall d. Data d => d -> u) -> Selector -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Selector -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Selector -> m Selector #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Selector -> m Selector #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Selector -> m Selector #

Ord Selector Source # 
Instance details

Defined in Css3.Selector.Core

Show Selector Source # 
Instance details

Defined in Css3.Selector.Core

Generic Selector Source # 
Instance details

Defined in Css3.Selector.Core

Associated Types

type Rep Selector :: Type -> Type #

Methods

from :: Selector -> Rep Selector x #

to :: Rep Selector x -> Selector #

Semigroup Selector Source # 
Instance details

Defined in Css3.Selector.Core

Arbitrary Selector Source # 
Instance details

Defined in Css3.Selector.Core

Hashable Selector Source # 
Instance details

Defined in Css3.Selector.Core

Methods

hashWithSalt :: Int -> Selector -> Int #

hash :: Selector -> Int #

ToJSON Selector Source # 
Instance details

Defined in Css3.Selector.Core

Binary Selector Source # 
Instance details

Defined in Css3.Selector.Core

Methods

put :: Selector -> Put #

get :: Get Selector #

putList :: [Selector] -> Put #

ToMarkup Selector Source # 
Instance details

Defined in Css3.Selector.Core

Default Selector Source # 
Instance details

Defined in Css3.Selector.Core

Methods

def :: Selector #

ToJavascript Selector Source # 
Instance details

Defined in Css3.Selector.Core

ToCssSelector Selector Source # 
Instance details

Defined in Css3.Selector.Core

Lift Selector Source # 
Instance details

Defined in Css3.Selector.Core

type Rep Selector Source # 
Instance details

Defined in Css3.Selector.Core

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 > in css.

DirectlyPreceded

The second tag is directly preceded by the first one, denoted with a + in css.

Preceded

The second tag is preceded by the first one, denoted with a ~ in css.

Instances

Instances details
Bounded SelectorCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Enum SelectorCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Eq SelectorCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Data SelectorCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SelectorCombinator -> c SelectorCombinator #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SelectorCombinator #

toConstr :: SelectorCombinator -> Constr #

dataTypeOf :: SelectorCombinator -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SelectorCombinator) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SelectorCombinator) #

gmapT :: (forall b. Data b => b -> b) -> SelectorCombinator -> SelectorCombinator #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SelectorCombinator -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SelectorCombinator -> r #

gmapQ :: (forall d. Data d => d -> u) -> SelectorCombinator -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SelectorCombinator -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SelectorCombinator -> m SelectorCombinator #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectorCombinator -> m SelectorCombinator #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectorCombinator -> m SelectorCombinator #

Ord SelectorCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Read SelectorCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Show SelectorCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Generic SelectorCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Associated Types

type Rep SelectorCombinator :: Type -> Type #

Arbitrary SelectorCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Hashable SelectorCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Binary SelectorCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Default SelectorCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Lift SelectorCombinator Source # 
Instance details

Defined in Css3.Selector.Core

type Rep SelectorCombinator Source # 
Instance details

Defined in Css3.Selector.Core

type Rep SelectorCombinator = D1 ('MetaData "SelectorCombinator" "Css3.Selector.Core" "css-selectors-0.4.0.3-1ASkwBXKE34AZInWNChBsH" 'False) ((C1 ('MetaCons "Descendant" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Child" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DirectlyPreceded" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Preceded" 'PrefixI 'False) (U1 :: Type -> Type)))

newtype SelectorGroup Source #

The root type of a css selector. This is a comma-separated list of selectors.

Constructors

SelectorGroup 

Fields

Instances

Instances details
IsList SelectorGroup Source # 
Instance details

Defined in Css3.Selector.Core

Associated Types

type Item SelectorGroup #

Eq SelectorGroup Source # 
Instance details

Defined in Css3.Selector.Core

Data SelectorGroup Source # 
Instance details

Defined in Css3.Selector.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SelectorGroup -> c SelectorGroup #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SelectorGroup #

toConstr :: SelectorGroup -> Constr #

dataTypeOf :: SelectorGroup -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SelectorGroup) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SelectorGroup) #

gmapT :: (forall b. Data b => b -> b) -> SelectorGroup -> SelectorGroup #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SelectorGroup -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SelectorGroup -> r #

gmapQ :: (forall d. Data d => d -> u) -> SelectorGroup -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SelectorGroup -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SelectorGroup -> m SelectorGroup #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectorGroup -> m SelectorGroup #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectorGroup -> m SelectorGroup #

Ord SelectorGroup Source # 
Instance details

Defined in Css3.Selector.Core

Show SelectorGroup Source # 
Instance details

Defined in Css3.Selector.Core

Generic SelectorGroup Source # 
Instance details

Defined in Css3.Selector.Core

Associated Types

type Rep SelectorGroup :: Type -> Type #

Semigroup SelectorGroup Source # 
Instance details

Defined in Css3.Selector.Core

Arbitrary SelectorGroup Source # 
Instance details

Defined in Css3.Selector.Core

Hashable SelectorGroup Source # 
Instance details

Defined in Css3.Selector.Core

ToJSON SelectorGroup Source # 
Instance details

Defined in Css3.Selector.Core

Binary SelectorGroup Source # 
Instance details

Defined in Css3.Selector.Core

ToMarkup SelectorGroup Source # 
Instance details

Defined in Css3.Selector.Core

Default SelectorGroup Source # 
Instance details

Defined in Css3.Selector.Core

Methods

def :: SelectorGroup #

ToJavascript SelectorGroup Source # 
Instance details

Defined in Css3.Selector.Core

ToCssSelector SelectorGroup Source # 
Instance details

Defined in Css3.Selector.Core

Lift SelectorGroup Source # 
Instance details

Defined in Css3.Selector.Core

type Rep SelectorGroup Source # 
Instance details

Defined in Css3.Selector.Core

type Rep SelectorGroup = D1 ('MetaData "SelectorGroup" "Css3.Selector.Core" "css-selectors-0.4.0.3-1ASkwBXKE34AZInWNChBsH" 'True) (C1 ('MetaCons "SelectorGroup" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSelectorGroup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Selector))))
type Item SelectorGroup Source # 
Instance details

Defined in Css3.Selector.Core

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.

Instances

Instances details
Eq SelectorSequence Source # 
Instance details

Defined in Css3.Selector.Core

Data SelectorSequence Source # 
Instance details

Defined in Css3.Selector.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SelectorSequence -> c SelectorSequence #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SelectorSequence #

toConstr :: SelectorSequence -> Constr #

dataTypeOf :: SelectorSequence -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SelectorSequence) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SelectorSequence) #

gmapT :: (forall b. Data b => b -> b) -> SelectorSequence -> SelectorSequence #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SelectorSequence -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SelectorSequence -> r #

gmapQ :: (forall d. Data d => d -> u) -> SelectorSequence -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SelectorSequence -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SelectorSequence -> m SelectorSequence #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectorSequence -> m SelectorSequence #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectorSequence -> m SelectorSequence #

Ord SelectorSequence Source # 
Instance details

Defined in Css3.Selector.Core

Show SelectorSequence Source # 
Instance details

Defined in Css3.Selector.Core

Generic SelectorSequence Source # 
Instance details

Defined in Css3.Selector.Core

Associated Types

type Rep SelectorSequence :: Type -> Type #

Arbitrary SelectorSequence Source # 
Instance details

Defined in Css3.Selector.Core

Hashable SelectorSequence Source # 
Instance details

Defined in Css3.Selector.Core

ToJSON SelectorSequence Source # 
Instance details

Defined in Css3.Selector.Core

Binary SelectorSequence Source # 
Instance details

Defined in Css3.Selector.Core

ToMarkup SelectorSequence Source # 
Instance details

Defined in Css3.Selector.Core

Default SelectorSequence Source # 
Instance details

Defined in Css3.Selector.Core

ToJavascript SelectorSequence Source # 
Instance details

Defined in Css3.Selector.Core

ToCssSelector SelectorSequence Source # 
Instance details

Defined in Css3.Selector.Core

Lift SelectorSequence Source # 
Instance details

Defined in Css3.Selector.Core

type Rep SelectorSequence Source # 
Instance details

Defined in Css3.Selector.Core

combinatorText Source #

Arguments

:: SelectorCombinator

The given SelectorCombinator to retrieve the css token for.

-> Text

The css selector token that is used for the given SelectorCombinator.

Convert the SelectorCombinator to the equivalent css selector text. A space for Descendant, a > for Child, a + for DirectlyPreceded, and a ~ for Preceded

combine Source #

Arguments

:: SelectorCombinator

The SelectorCombinator that is applied between the two Selectors.

-> Selector

The left Selector.

-> Selector

The right Selector.

-> Selector

A Selector that is a combination of the left Selector and the right Selector with the given SelectorCombinator.

Combines two Selectors with the given SelectorCombinator.

(.>) Source #

Arguments

:: Selector

The left Selector.

-> Selector

The right Selector.

-> Selector

A selector that is the combination of the left Selector and the right Selector through Child.

Combines two Selectors with the Child combinator.

(.+) Source #

Arguments

:: Selector

The left Selector.

-> Selector

The right Selector.

-> Selector

A selector that is the combination of the left Selector and the right Selector through DirectlyPreceded.

Combines two Selectors with the DirectlyPreceded combinator.

(.~) Source #

Arguments

:: Selector

The left Selector.

-> Selector

The right Selector.

-> Selector

A selector that is the combination of the left Selector and the right Selector through Preceded.

Combines two Selectors with the Preceded 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 Hash object as filter.

SClass Class

A Class object as filter.

SAttrib Attrib

An Attrib object as filter.

Instances

Instances details
Eq SelectorFilter Source # 
Instance details

Defined in Css3.Selector.Core

Data SelectorFilter Source # 
Instance details

Defined in Css3.Selector.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SelectorFilter -> c SelectorFilter #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SelectorFilter #

toConstr :: SelectorFilter -> Constr #

dataTypeOf :: SelectorFilter -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SelectorFilter) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SelectorFilter) #

gmapT :: (forall b. Data b => b -> b) -> SelectorFilter -> SelectorFilter #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SelectorFilter -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SelectorFilter -> r #

gmapQ :: (forall d. Data d => d -> u) -> SelectorFilter -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SelectorFilter -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SelectorFilter -> m SelectorFilter #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectorFilter -> m SelectorFilter #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectorFilter -> m SelectorFilter #

Ord SelectorFilter Source # 
Instance details

Defined in Css3.Selector.Core

Show SelectorFilter Source # 
Instance details

Defined in Css3.Selector.Core

Generic SelectorFilter Source # 
Instance details

Defined in Css3.Selector.Core

Associated Types

type Rep SelectorFilter :: Type -> Type #

Arbitrary SelectorFilter Source # 
Instance details

Defined in Css3.Selector.Core

Hashable SelectorFilter Source # 
Instance details

Defined in Css3.Selector.Core

ToJSON SelectorFilter Source # 
Instance details

Defined in Css3.Selector.Core

Binary SelectorFilter Source # 
Instance details

Defined in Css3.Selector.Core

ToMarkup SelectorFilter Source # 
Instance details

Defined in Css3.Selector.Core

ToJavascript SelectorFilter Source # 
Instance details

Defined in Css3.Selector.Core

ToCssSelector SelectorFilter Source # 
Instance details

Defined in Css3.Selector.Core

Lift SelectorFilter Source # 
Instance details

Defined in Css3.Selector.Core

type Rep SelectorFilter Source # 
Instance details

Defined in Css3.Selector.Core

filters Source #

Arguments

:: SelectorSequence

The given SelectorSequence to analyze.

-> [SelectorFilter]

The given list of SelectorFilters applied, this can be empty.

Obtain the list of filters that are applied in the given SelectorSequence.

filters' Source #

Arguments

:: SelectorSequence

The given SelectorSequence to analyze.

-> [SelectorFilter]

The given list of SelectorFilters applied in reversed order, this can be empty.

Obtain the list of filters that are applied in the given SelectorSequence in reversed order.

addFilters Source #

Arguments

:: SelectorSequence

The SelectorSequence to apply the filter on.

-> [SelectorFilter]

The list of SelectorFilters to apply on the SelectorSequence.

-> SelectorSequence

A modified SelectorSequence where we applied the list of SelectorFilters.

Add a given list of SelectorFilters to the given SelectorSequence. The filters are applied left-to-right.

(.:) Source #

Arguments

:: SelectorSequence

The SelectorSequence to apply the filter on.

-> [SelectorFilter]

The list of SelectorFilters to apply on the SelectorSequence.

-> SelectorSequence

A modified SelectorSequence where we applied the list of SelectorFilters.

An infix variant of the addFilters function.

Namespaces

data Namespace Source #

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

Instances details
Eq Namespace Source # 
Instance details

Defined in Css3.Selector.Core

Data Namespace Source # 
Instance details

Defined in Css3.Selector.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Namespace -> c Namespace #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Namespace #

toConstr :: Namespace -> Constr #

dataTypeOf :: Namespace -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Namespace) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Namespace) #

gmapT :: (forall b. Data b => b -> b) -> Namespace -> Namespace #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Namespace -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Namespace -> r #

gmapQ :: (forall d. Data d => d -> u) -> Namespace -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Namespace -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Namespace -> m Namespace #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Namespace -> m Namespace #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Namespace -> m Namespace #

Ord Namespace Source # 
Instance details

Defined in Css3.Selector.Core

Show Namespace Source # 
Instance details

Defined in Css3.Selector.Core

IsString Namespace Source # 
Instance details

Defined in Css3.Selector.Core

Generic Namespace Source # 
Instance details

Defined in Css3.Selector.Core

Associated Types

type Rep Namespace :: Type -> Type #

Semigroup Namespace Source # 
Instance details

Defined in Css3.Selector.Core

Monoid Namespace Source # 
Instance details

Defined in Css3.Selector.Core

Arbitrary Namespace Source # 
Instance details

Defined in Css3.Selector.Core

Hashable Namespace Source # 
Instance details

Defined in Css3.Selector.Core

Binary Namespace Source # 
Instance details

Defined in Css3.Selector.Core

Default Namespace Source # 
Instance details

Defined in Css3.Selector.Core

Methods

def :: Namespace #

ToCssSelector Namespace Source # 
Instance details

Defined in Css3.Selector.Core

type Rep Namespace Source # 
Instance details

Defined in Css3.Selector.Core

type Rep Namespace = D1 ('MetaData "Namespace" "Css3.Selector.Core" "css-selectors-0.4.0.3-1ASkwBXKE34AZInWNChBsH" 'False) (C1 ('MetaCons "NAny" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Namespace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

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

Instances details
Eq ElementName Source # 
Instance details

Defined in Css3.Selector.Core

Data ElementName Source # 
Instance details

Defined in Css3.Selector.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ElementName -> c ElementName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ElementName #

toConstr :: ElementName -> Constr #

dataTypeOf :: ElementName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ElementName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ElementName) #

gmapT :: (forall b. Data b => b -> b) -> ElementName -> ElementName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ElementName -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ElementName -> r #

gmapQ :: (forall d. Data d => d -> u) -> ElementName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ElementName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ElementName -> m ElementName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ElementName -> m ElementName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ElementName -> m ElementName #

Ord ElementName Source # 
Instance details

Defined in Css3.Selector.Core

Show ElementName Source # 
Instance details

Defined in Css3.Selector.Core

IsString ElementName Source # 
Instance details

Defined in Css3.Selector.Core

Generic ElementName Source # 
Instance details

Defined in Css3.Selector.Core

Associated Types

type Rep ElementName :: Type -> Type #

Semigroup ElementName Source # 
Instance details

Defined in Css3.Selector.Core

Monoid ElementName Source # 
Instance details

Defined in Css3.Selector.Core

Arbitrary ElementName Source # 
Instance details

Defined in Css3.Selector.Core

Hashable ElementName Source # 
Instance details

Defined in Css3.Selector.Core

Binary ElementName Source # 
Instance details

Defined in Css3.Selector.Core

Default ElementName Source # 
Instance details

Defined in Css3.Selector.Core

Methods

def :: ElementName #

ToCssSelector ElementName Source # 
Instance details

Defined in Css3.Selector.Core

type Rep ElementName Source # 
Instance details

Defined in Css3.Selector.Core

type Rep ElementName = D1 ('MetaData "ElementName" "Css3.Selector.Core" "css-selectors-0.4.0.3-1ASkwBXKE34AZInWNChBsH" 'False) (C1 ('MetaCons "EAny" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ElementName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

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

Instances details
Eq TypeSelector Source # 
Instance details

Defined in Css3.Selector.Core

Data TypeSelector Source # 
Instance details

Defined in Css3.Selector.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeSelector -> c TypeSelector #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeSelector #

toConstr :: TypeSelector -> Constr #

dataTypeOf :: TypeSelector -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeSelector) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeSelector) #

gmapT :: (forall b. Data b => b -> b) -> TypeSelector -> TypeSelector #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeSelector -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeSelector -> r #

gmapQ :: (forall d. Data d => d -> u) -> TypeSelector -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeSelector -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeSelector -> m TypeSelector #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeSelector -> m TypeSelector #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeSelector -> m TypeSelector #

Ord TypeSelector Source # 
Instance details

Defined in Css3.Selector.Core

Show TypeSelector Source # 
Instance details

Defined in Css3.Selector.Core

Generic TypeSelector Source # 
Instance details

Defined in Css3.Selector.Core

Associated Types

type Rep TypeSelector :: Type -> Type #

Arbitrary TypeSelector Source # 
Instance details

Defined in Css3.Selector.Core

Hashable TypeSelector Source # 
Instance details

Defined in Css3.Selector.Core

Binary TypeSelector Source # 
Instance details

Defined in Css3.Selector.Core

Default TypeSelector Source # 
Instance details

Defined in Css3.Selector.Core

Methods

def :: TypeSelector #

ToCssSelector TypeSelector Source # 
Instance details

Defined in Css3.Selector.Core

type Rep TypeSelector Source # 
Instance details

Defined in Css3.Selector.Core

type Rep TypeSelector = D1 ('MetaData "TypeSelector" "Css3.Selector.Core" "css-selectors-0.4.0.3-1ASkwBXKE34AZInWNChBsH" 'False) (C1 ('MetaCons "TypeSelector" 'PrefixI 'True) (S1 ('MetaSel ('Just "selectorNamespace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Namespace) :*: S1 ('MetaSel ('Just "elementName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ElementName)))

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.

(.|) Source #

Arguments

:: Namespace

The Namespace for the TypeSelector.

-> ElementName

The ElementName for the TypeSelector.

-> TypeSelector

A TypeSelector object constructed with the Namespace and ElementName.

Construct a TypeSelector with a given Namespace and ElementName.

Attributes

data Attrib Source #

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 AttributeName should exist.

Attrib AttributeName AttributeCombinator AttributeValue

A constraint about the value associated with the given AttributeName.

Instances

Instances details
Eq Attrib Source # 
Instance details

Defined in Css3.Selector.Core

Methods

(==) :: Attrib -> Attrib -> Bool #

(/=) :: Attrib -> Attrib -> Bool #

Data Attrib Source # 
Instance details

Defined in Css3.Selector.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Attrib -> c Attrib #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Attrib #

toConstr :: Attrib -> Constr #

dataTypeOf :: Attrib -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Attrib) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Attrib) #

gmapT :: (forall b. Data b => b -> b) -> Attrib -> Attrib #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Attrib -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Attrib -> r #

gmapQ :: (forall d. Data d => d -> u) -> Attrib -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Attrib -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Attrib -> m Attrib #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Attrib -> m Attrib #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Attrib -> m Attrib #

Ord Attrib Source # 
Instance details

Defined in Css3.Selector.Core

Show Attrib Source # 
Instance details

Defined in Css3.Selector.Core

IsString Attrib Source # 
Instance details

Defined in Css3.Selector.Core

Methods

fromString :: String -> Attrib #

Generic Attrib Source # 
Instance details

Defined in Css3.Selector.Core

Associated Types

type Rep Attrib :: Type -> Type #

Methods

from :: Attrib -> Rep Attrib x #

to :: Rep Attrib x -> Attrib #

Arbitrary Attrib Source # 
Instance details

Defined in Css3.Selector.Core

Hashable Attrib Source # 
Instance details

Defined in Css3.Selector.Core

Methods

hashWithSalt :: Int -> Attrib -> Int #

hash :: Attrib -> Int #

ToJSON Attrib Source # 
Instance details

Defined in Css3.Selector.Core

Binary Attrib Source # 
Instance details

Defined in Css3.Selector.Core

Methods

put :: Attrib -> Put #

get :: Get Attrib #

putList :: [Attrib] -> Put #

ToMarkup Attrib Source # 
Instance details

Defined in Css3.Selector.Core

ToJavascript Attrib Source # 
Instance details

Defined in Css3.Selector.Core

ToCssSelector Attrib Source # 
Instance details

Defined in Css3.Selector.Core

Lift Attrib Source # 
Instance details

Defined in Css3.Selector.Core

Methods

lift :: Attrib -> Q Exp #

liftTyped :: Attrib -> Q (TExp Attrib) #

type Rep Attrib Source # 
Instance details

Defined in Css3.Selector.Core

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 = in css.

Include

The attribute has a whitespace separated list of items, one of these items is the value, denoted with ~= in css.

DashMatch

The attribute has a hyphen separated list of items, the first item is the value, denoted with |= in css.

PrefixMatch

The value is a prefix of the value in the attribute, denoted with ^= in css.

SuffixMatch

The value is a suffix of the value in the attribute, denoted with $= in css.

SubstringMatch

The value is a substring of the value in the attribute, denoted with *= in css.

Instances

Instances details
Bounded AttributeCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Enum AttributeCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Eq AttributeCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Data AttributeCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AttributeCombinator -> c AttributeCombinator #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AttributeCombinator #

toConstr :: AttributeCombinator -> Constr #

dataTypeOf :: AttributeCombinator -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AttributeCombinator) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AttributeCombinator) #

gmapT :: (forall b. Data b => b -> b) -> AttributeCombinator -> AttributeCombinator #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AttributeCombinator -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AttributeCombinator -> r #

gmapQ :: (forall d. Data d => d -> u) -> AttributeCombinator -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AttributeCombinator -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AttributeCombinator -> m AttributeCombinator #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AttributeCombinator -> m AttributeCombinator #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AttributeCombinator -> m AttributeCombinator #

Ord AttributeCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Read AttributeCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Show AttributeCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Generic AttributeCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Associated Types

type Rep AttributeCombinator :: Type -> Type #

Arbitrary AttributeCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Hashable AttributeCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Binary AttributeCombinator Source # 
Instance details

Defined in Css3.Selector.Core

Default AttributeCombinator Source # 
Instance details

Defined in Css3.Selector.Core

type Rep AttributeCombinator Source # 
Instance details

Defined in Css3.Selector.Core

type Rep AttributeCombinator = D1 ('MetaData "AttributeCombinator" "Css3.Selector.Core" "css-selectors-0.4.0.3-1ASkwBXKE34AZInWNChBsH" 'False) ((C1 ('MetaCons "Exact" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Include" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DashMatch" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "PrefixMatch" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SuffixMatch" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SubstringMatch" 'PrefixI 'False) (U1 :: Type -> Type))))

data AttributeName Source #

An attribute name is a name that optionally has a namespace, and the name of the attribute.

Constructors

AttributeName 

Fields

Instances

Instances details
Eq AttributeName Source # 
Instance details

Defined in Css3.Selector.Core

Data AttributeName Source # 
Instance details

Defined in Css3.Selector.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AttributeName -> c AttributeName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AttributeName #

toConstr :: AttributeName -> Constr #

dataTypeOf :: AttributeName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AttributeName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AttributeName) #

gmapT :: (forall b. Data b => b -> b) -> AttributeName -> AttributeName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AttributeName -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AttributeName -> r #

gmapQ :: (forall d. Data d => d -> u) -> AttributeName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AttributeName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AttributeName -> m AttributeName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AttributeName -> m AttributeName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AttributeName -> m AttributeName #

Ord AttributeName Source # 
Instance details

Defined in Css3.Selector.Core

Show AttributeName Source # 
Instance details

Defined in Css3.Selector.Core

IsString AttributeName Source # 
Instance details

Defined in Css3.Selector.Core

Generic AttributeName Source # 
Instance details

Defined in Css3.Selector.Core

Associated Types

type Rep AttributeName :: Type -> Type #

Arbitrary AttributeName Source # 
Instance details

Defined in Css3.Selector.Core

Hashable AttributeName Source # 
Instance details

Defined in Css3.Selector.Core

Binary AttributeName Source # 
Instance details

Defined in Css3.Selector.Core

ToCssSelector AttributeName Source # 
Instance details

Defined in Css3.Selector.Core

type Rep AttributeName Source # 
Instance details

Defined in Css3.Selector.Core

type Rep AttributeName = D1 ('MetaData "AttributeName" "Css3.Selector.Core" "css-selectors-0.4.0.3-1ASkwBXKE34AZInWNChBsH" 'False) (C1 ('MetaCons "AttributeName" 'PrefixI 'True) (S1 ('MetaSel ('Just "attributeNamespace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Namespace) :*: S1 ('MetaSel ('Just "attributeName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

type AttributeValue = Text Source #

We use Text as the type to store an attribute value.

(.=) Source #

Arguments

:: AttributeName

The name of the attribute to constraint.

-> AttributeValue

The value that constraints the attribute.

-> Attrib

The Attrib object we construct with the given name and value.

Create an Attrib where the given AttributeName is constrainted to be exactly the given value.

(.~=) Source #

Arguments

:: AttributeName

The name of the attribute to constraint.

-> AttributeValue

The value that constraints the attribute.

-> Attrib

The Attrib object we construct with the given name and value.

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.

(.|=) Source #

Arguments

:: AttributeName

The name of the attribute to constraint.

-> AttributeValue

The value that constraints the attribute.

-> Attrib

The Attrib object we construct with the given name and value.

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.

(.^=) Source #

Arguments

:: AttributeName

The name of the attribute to constraint.

-> AttributeValue

The value that constraints the attribute.

-> Attrib

The Attrib object we construct with the given name and value.

Create an Attrib where the given AttributeName is constrainted such that the attribute has as prefix the given AttributeValue.

(.$=) Source #

Arguments

:: AttributeName

The name of the attribute to constraint.

-> AttributeValue

The value that constraints the attribute.

-> Attrib

The Attrib object we construct with the given name and value.

Create an Attrib where the given AttributeName is constrainted such that the attribute has as suffix the given AttributeValue.

(.*=) Source #

Arguments

:: AttributeName

The name of the attribute to constraint.

-> AttributeValue

The value that constraints the attribute.

-> Attrib

The Attrib object we construct with the given name and value.

Create an Attrib where the given AttributeName is constrainted such that the attribute has as substring the given AttributeValue.

attrib Source #

Arguments

:: AttributeCombinator

The AttributeCombinator that specifies the required relation between the attribute and a value.

-> AttributeName

The name of an attribute to filter.

-> AttributeValue

The value of the attribute to filter.

-> Attrib

The result is an Attrib object that will filter the given AttributeName with the given AttributeCombinator.

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 AttributeCombinator for which we obtain the corresponding css selector text.

-> AttributeValue

The css selector text for the given AttributeCombinator.

Convert the given AttributeCombinator to its css selector counterpart.

Classes

newtype Class Source #

A css class, this is wrapped in a data type. The type only wraps the class name, not the dot prefix.

Constructors

Class 

Fields

Instances

Instances details
Eq Class Source # 
Instance details

Defined in Css3.Selector.Core

Methods

(==) :: Class -> Class -> Bool #

(/=) :: Class -> Class -> Bool #

Data Class Source # 
Instance details

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 #

toConstr :: Class -> Constr #

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 #

Ord Class Source # 
Instance details

Defined in Css3.Selector.Core

Methods

compare :: Class -> Class -> Ordering #

(<) :: Class -> Class -> Bool #

(<=) :: Class -> Class -> Bool #

(>) :: Class -> Class -> Bool #

(>=) :: Class -> Class -> Bool #

max :: Class -> Class -> Class #

min :: Class -> Class -> Class #

Show Class Source # 
Instance details

Defined in Css3.Selector.Core

Methods

showsPrec :: Int -> Class -> ShowS #

show :: Class -> String #

showList :: [Class] -> ShowS #

IsString Class Source # 
Instance details

Defined in Css3.Selector.Core

Methods

fromString :: String -> Class #

Generic Class Source # 
Instance details

Defined in Css3.Selector.Core

Associated Types

type Rep Class :: Type -> Type #

Methods

from :: Class -> Rep Class x #

to :: Rep Class x -> Class #

Arbitrary Class Source # 
Instance details

Defined in Css3.Selector.Core

Methods

arbitrary :: Gen Class #

shrink :: Class -> [Class] #

Hashable Class Source # 
Instance details

Defined in Css3.Selector.Core

Methods

hashWithSalt :: Int -> Class -> Int #

hash :: Class -> Int #

Binary Class Source # 
Instance details

Defined in Css3.Selector.Core

Methods

put :: Class -> Put #

get :: Get Class #

putList :: [Class] -> Put #

ToCssSelector Class Source # 
Instance details

Defined in Css3.Selector.Core

type Rep Class Source # 
Instance details

Defined in Css3.Selector.Core

type Rep Class = D1 ('MetaData "Class" "Css3.Selector.Core" "css-selectors-0.4.0.3-1ASkwBXKE34AZInWNChBsH" 'True) (C1 ('MetaCons "Class" 'PrefixI 'True) (S1 ('MetaSel ('Just "unClass") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

(...) Source #

Arguments

:: SelectorSequence

The given 'SelectorSequence to filter.

-> Class

The given Class to filter the SelectorSequence further.

-> SelectorSequence

A SelectorSequence that is filtered additionally with the given Class.

Filter a given SelectorSequence with a given Class.

Hashes

newtype Hash Source #

A css hash (used to match an element with a given id). The type only wraps the hash name, not the hash (#) prefix.

Constructors

Hash 

Fields

Instances

Instances details
Eq Hash Source # 
Instance details

Defined in Css3.Selector.Core

Methods

(==) :: Hash -> Hash -> Bool #

(/=) :: Hash -> Hash -> Bool #

Data Hash Source # 
Instance details

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 #

toConstr :: Hash -> Constr #

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 #

Ord Hash Source # 
Instance details

Defined in Css3.Selector.Core

Methods

compare :: Hash -> Hash -> Ordering #

(<) :: Hash -> Hash -> Bool #

(<=) :: Hash -> Hash -> Bool #

(>) :: Hash -> Hash -> Bool #

(>=) :: Hash -> Hash -> Bool #

max :: Hash -> Hash -> Hash #

min :: Hash -> Hash -> Hash #

Show Hash Source # 
Instance details

Defined in Css3.Selector.Core

Methods

showsPrec :: Int -> Hash -> ShowS #

show :: Hash -> String #

showList :: [Hash] -> ShowS #

IsString Hash Source # 
Instance details

Defined in Css3.Selector.Core

Methods

fromString :: String -> Hash #

Generic Hash Source # 
Instance details

Defined in Css3.Selector.Core

Associated Types

type Rep Hash :: Type -> Type #

Methods

from :: Hash -> Rep Hash x #

to :: Rep Hash x -> Hash #

Arbitrary Hash Source # 
Instance details

Defined in Css3.Selector.Core

Methods

arbitrary :: Gen Hash #

shrink :: Hash -> [Hash] #

Hashable Hash Source # 
Instance details

Defined in Css3.Selector.Core

Methods

hashWithSalt :: Int -> Hash -> Int #

hash :: Hash -> Int #

Binary Hash Source # 
Instance details

Defined in Css3.Selector.Core

Methods

put :: Hash -> Put #

get :: Get Hash #

putList :: [Hash] -> Put #

ToCssSelector Hash Source # 
Instance details

Defined in Css3.Selector.Core

type Rep Hash Source # 
Instance details

Defined in Css3.Selector.Core

type Rep Hash = D1 ('MetaData "Hash" "Css3.Selector.Core" "css-selectors-0.4.0.3-1ASkwBXKE34AZInWNChBsH" 'True) (C1 ('MetaCons "Hash" 'PrefixI 'True) (S1 ('MetaSel ('Just "unHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

(.#) Source #

Arguments

:: SelectorSequence

The given SelectorSequence to filter.

-> Hash

The given Hash to filter the SelectorSequence further.

-> SelectorSequence

A SelectorSequence that is filtered additionally with the given Hash.

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.

Constructors

SelectorSpecificity Int Int Int

Create a SelectorSpecificity object with a given value for a, b, and c.

Instances

Instances details
Eq SelectorSpecificity Source # 
Instance details

Defined in Css3.Selector.Core

Data SelectorSpecificity Source # 
Instance details

Defined in Css3.Selector.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SelectorSpecificity -> c SelectorSpecificity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SelectorSpecificity #

toConstr :: SelectorSpecificity -> Constr #

dataTypeOf :: SelectorSpecificity -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SelectorSpecificity) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SelectorSpecificity) #

gmapT :: (forall b. Data b => b -> b) -> SelectorSpecificity -> SelectorSpecificity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SelectorSpecificity -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SelectorSpecificity -> r #

gmapQ :: (forall d. Data d => d -> u) -> SelectorSpecificity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SelectorSpecificity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SelectorSpecificity -> m SelectorSpecificity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectorSpecificity -> m SelectorSpecificity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectorSpecificity -> m SelectorSpecificity #

Ord SelectorSpecificity Source # 
Instance details

Defined in Css3.Selector.Core

Show SelectorSpecificity Source # 
Instance details

Defined in Css3.Selector.Core

Generic SelectorSpecificity Source # 
Instance details

Defined in Css3.Selector.Core

Associated Types

type Rep SelectorSpecificity :: Type -> Type #

Semigroup SelectorSpecificity Source # 
Instance details

Defined in Css3.Selector.Core

Monoid SelectorSpecificity Source # 
Instance details

Defined in Css3.Selector.Core

Hashable SelectorSpecificity Source # 
Instance details

Defined in Css3.Selector.Core

Binary SelectorSpecificity Source # 
Instance details

Defined in Css3.Selector.Core

Default SelectorSpecificity Source # 
Instance details

Defined in Css3.Selector.Core

type Rep SelectorSpecificity Source # 
Instance details

Defined in Css3.Selector.Core

type Rep SelectorSpecificity = D1 ('MetaData "SelectorSpecificity" "Css3.Selector.Core" "css-selectors-0.4.0.3-1ASkwBXKE34AZInWNChBsH" 'False) (C1 ('MetaCons "SelectorSpecificity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))

specificity Source #

Arguments

:: ToCssSelector a 
=> a

The object for which we evaluate the specificity.

-> Int

The specificity level as an Int value.

Calculate the specificity of a ToCssSelector type object. This is done by calculating the SelectorSpecificity object, and then calculating the value of that object.

specificityValue Source #

Arguments

:: SelectorSpecificity

The SelectorSpecificity to calculate the specificity value from.

-> Int

The specificity level of the SelectorSpecificity. If the value is higher, the rules in the css selector take precedence.

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.

compressEncode Source #

Arguments

:: (Binary a, ToCssSelector a) 
=> a

The object to turn into a compressed ByteString.

-> 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.

compressEncodeWith Source #

Arguments

:: (Binary a, ToCssSelector a) 
=> CompressParams

The parameters that determine how to compress the ByteString.

-> a

The object to turn into a compressed ByteString.

-> 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.

decompressDecode Source #

Arguments

:: (Binary a, ToCssSelector a) 
=> ByteString

A compressed binary representation of a ToCssSelector type.

-> 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.