reanimate-svg-0.13.0.1: SVG file loader and serializer
Safe HaskellNone
LanguageHaskell2010

Graphics.SvgTree.CssTypes

Description

Defines the types used to describes CSS elements

Synopsis

Documentation

data CssSelector Source #

Defines complex selector.

Constructors

Nearby

Corresponds to the + CSS selector.

DirectChildren

Corresponds to the > CSS selectro.

AllOf [CssDescriptor]

Grouping construct, all the elements of the list must be matched.

Instances

Instances details
Eq CssSelector Source # 
Instance details

Defined in Graphics.SvgTree.CssTypes

Show CssSelector Source # 
Instance details

Defined in Graphics.SvgTree.CssTypes

type CssSelectorRule = [CssSelector] Source #

A CssSelectorRule is a list of all the elements that must be met in a depth first search fashion.

data CssRule Source #

Represents a CSS selector and the different declarations to apply to the matched elemens.

Constructors

CssRule 

Fields

Instances

Instances details
Eq CssRule Source # 
Instance details

Defined in Graphics.SvgTree.CssTypes

Methods

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

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

Show CssRule Source # 
Instance details

Defined in Graphics.SvgTree.CssTypes

data CssDescriptor Source #

Describes an element of a CSS selector. Multiple elements can be combined in a CssSelector type.

Constructors

OfClass Text

.IDENT

OfName Text

IDENT

OfId Text

#IDENT

OfPseudoClass Text

`:IDENT` (ignore function syntax)

AnyElem

*

WithAttrib Text Text

``

Instances

Instances details
Eq CssDescriptor Source # 
Instance details

Defined in Graphics.SvgTree.CssTypes

Show CssDescriptor Source # 
Instance details

Defined in Graphics.SvgTree.CssTypes

data CssDeclaration Source #

Represents the content to apply to some CSS matched rules.

Constructors

CssDeclaration 

Fields

data CssElement Source #

Value of a CSS property.

Instances

Instances details
Eq CssElement Source # 
Instance details

Defined in Graphics.SvgTree.CssTypes

Show CssElement Source # 
Instance details

Defined in Graphics.SvgTree.CssTypes

class CssMatcheable a where Source #

Interface for elements to be matched against some CssRule.

Methods

cssIdOf :: a -> Maybe Text Source #

For an element, tell its optional ID attribute.

cssClassOf :: a -> [Text] Source #

For an element, return all of it's class attributes.

cssNameOf :: a -> Text Source #

Return the name of the tagname of the element

cssAttribOf :: a -> Text -> Maybe Text Source #

Return a value of a given attribute if present

Instances

Instances details
CssMatcheable Tree Source # 
Instance details

Defined in Graphics.SvgTree.Types.Instances

type CssContext a = [[a]] Source #

Represents a zipper in depth at the first list level, and the previous nodes at in the second list level.

type Dpi = Int Source #

Alias describing a "dot per inch" information used for size calculation (see toUserUnit).

data Number Source #

Encode complex number possibly depending on the current render size.

Constructors

Num Double

Simple coordinate in current user coordinate.

Px Double

With suffix "px"

Em Double

Number relative to the current font size.

Percent Double

Number relative to the current viewport size.

Pc Double 
Mm Double

Number in millimeters, relative to DPI.

Cm Double

Number in centimeters, relative to DPI.

Point Double

Number in points, relative to DPI.

Inches Double

Number in inches, relative to DPI.

Instances

Instances details
Eq Number Source # 
Instance details

Defined in Graphics.SvgTree.CssTypes

Methods

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

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

Show Number Source # 
Instance details

Defined in Graphics.SvgTree.CssTypes

Generic Number Source # 
Instance details

Defined in Graphics.SvgTree.CssTypes

Associated Types

type Rep Number :: Type -> Type #

Methods

from :: Number -> Rep Number x #

to :: Rep Number x -> Number #

Hashable Number Source # 
Instance details

Defined in Graphics.SvgTree.CssTypes

Methods

hashWithSalt :: Int -> Number -> Int #

hash :: Number -> Int #

type Rep Number Source # 
Instance details

Defined in Graphics.SvgTree.CssTypes

type Rep Number = D1 ('MetaData "Number" "Graphics.SvgTree.CssTypes" "reanimate-svg-0.13.0.1-LCJdrqXCg704yy3oKmvLHb" 'False) (((C1 ('MetaCons "Num" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :+: C1 ('MetaCons "Px" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double))) :+: (C1 ('MetaCons "Em" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :+: C1 ('MetaCons "Percent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))) :+: ((C1 ('MetaCons "Pc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :+: C1 ('MetaCons "Mm" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double))) :+: (C1 ('MetaCons "Cm" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :+: (C1 ('MetaCons "Point" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :+: C1 ('MetaCons "Inches" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double))))))

serializeNumber :: Number -> String Source #

Encode the number to string which can be used in a CSS or a svg attributes.

findMatchingDeclarations :: CssMatcheable a => [CssRule] -> CssContext a -> [CssDeclaration] Source #

Given CSS rules, find all the declarations to apply to the element in a given context.

toUserUnit :: Dpi -> Number -> Number Source #

This function replaces all device dependant units with user units given its DPI configuration. Preserves percentage and "em" notation.

mapNumber :: (Double -> Double) -> Number -> Number Source #

Helper function to modify inner value of a number

tserialize :: TextBuildable a => a -> Builder Source #

Serialize an element to a text builder.