hxt-7.3: A collection of tools for processing XML with Haskell.ContentsIndex
Text.XML.HXT.XSLT.CompiledStylesheet
Portabilityportable
Stabilityexperimental
MaintainerUwe Schmidt (uwe\@fh-wedel.de)
Description

Version : $Id: CompiledStylesheet.hs,v 1.3 20070502 06:41:05 hxml Exp $

Types for compiled stylesheets

Documentation
data CompiledStylesheet
Constructors
CompStylesheet [MatchRule] (Map ExName NamedRule) (Map ExName Variable) (Map ExName [AttributeSet]) [Strips] NSAliasing
show/hide Instances
getMatchRules :: CompiledStylesheet -> [MatchRule]
getNamedRules :: CompiledStylesheet -> Map ExName NamedRule
getVariables :: CompiledStylesheet -> Map ExName Variable
getAttributeSets :: CompiledStylesheet -> Map ExName [AttributeSet]
getStrips :: CompiledStylesheet -> [Strips]
getAliases :: CompiledStylesheet -> NSAliasing
data MatchRule
Constructors
MatRule MatchExpr Float (Maybe ExName) [MatchRule] [Variable] Template
show/hide Instances
getRulePrio :: MatchRule -> Float
getRuleMode :: MatchRule -> Maybe ExName
getRuleImports :: MatchRule -> [MatchRule]
data NamedRule
Constructors
NamRule ExName [Variable] Template
show/hide Instances
getRuleName :: NamedRule -> ExName
data Variable
Constructors
MkVar Bool ExName (Either Expr Template)
show/hide Instances
getVarName :: Variable -> ExName
isParam :: Variable -> Bool
newtype UsedAttribSets
Constructors
UsedAttribSets [ExName]
show/hide Instances
data AttributeSet
Constructors
AttribSet ExName UsedAttribSets Template
show/hide Instances
type NTest = ExName
parseNTest :: UriMapping -> String -> NTest
type Strips = Map NTest Bool
lookupStrip :: ExName -> [Strips] -> Bool
lookupStrip1 :: ExName -> Strips -> Maybe Bool
feedSpaces :: Bool -> [NTest] -> Strips -> Strips
feedStrips :: [NTest] -> Strips -> Strips
feedPreserves :: [NTest] -> Strips -> Strips
stripDocument :: [Strips] -> XmlTree -> XmlTree
stripStylesheet :: XmlTree -> XmlTree
stripSpaces :: (Bool -> XNode -> Bool) -> Bool -> XmlTree -> XmlTree
type NSAliasing = Map String String
addAlias :: UriMapping -> String -> String -> NSAliasing -> NSAliasing
lookupAlias :: NSAliasing -> QName -> QName
aliasUriMapping :: NSAliasing -> UriMapping -> UriMapping
data Template
Constructors
TemplComposite [Template]
TemplForEach SelectExpr [SortKey] Template
TemplChoose [When]
TemplMessage Bool Template
TemplElement ComputedQName UriMapping UsedAttribSets Template
TemplAttribute ComputedQName Template
TemplText String
TemplValueOf StringExpr
TemplComment Template
TemplProcInstr StringExpr Template
TemplApply (Maybe SelectExpr) (Maybe ExName) (Map ExName Variable) [SortKey]
TemplApplyImports
TemplVariable Variable
TemplCall ExName (Map ExName Variable)
TemplCopy UsedAttribSets Template
TemplCopyOf Expr
show/hide Instances
data SortKey
Constructors
SortK StringExpr StringExpr StringExpr
show/hide Instances
data When
Constructors
WhenPart TestExpr Template
show/hide Instances
data ComputedQName
Constructors
LiteralQName QName
CompQName UriMapping StringExpr StringExpr
show/hide Instances
newtype SelectExpr
Constructors
SelectExpr Expr
show/hide Instances
newtype TestExpr
Constructors
TestExpr Expr
show/hide Instances
newtype StringExpr
Constructors
StringExpr Expr
show/hide Instances
newtype MatchExpr
Constructors
MatchExpr Expr
show/hide Instances
Produced by Haddock version 0.8