hxt-9.3.1.18: A collection of tools for processing XML with Haskell.

CopyrightCopyright (C) 2010 Uwe Schmidt
LicenseMIT
MaintainerUwe Schmidt (uwe\@fh-wedel.de)
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Control.Arrow.StateListArrow

Description

Implementation of list arrows with a state

Synopsis

Documentation

newtype SLA s a b Source #

list arrow combined with a state

Constructors

SLA 

Fields

  • runSLA :: s -> a -> (s, [b])
     
Instances
ArrowState s (SLA s) Source # 
Instance details

Defined in Control.Arrow.StateListArrow

Methods

changeState :: (s -> b -> s) -> SLA s b b Source #

accessState :: (s -> b -> c) -> SLA s b c Source #

getState :: SLA s b s Source #

setState :: SLA s s s Source #

nextState :: (s -> s) -> SLA s b s Source #

Arrow (SLA s) Source # 
Instance details

Defined in Control.Arrow.StateListArrow

Methods

arr :: (b -> c) -> SLA s b c #

first :: SLA s b c -> SLA s (b, d) (c, d) #

second :: SLA s b c -> SLA s (d, b) (d, c) #

(***) :: SLA s b c -> SLA s b' c' -> SLA s (b, b') (c, c') #

(&&&) :: SLA s b c -> SLA s b c' -> SLA s b (c, c') #

ArrowZero (SLA s) Source # 
Instance details

Defined in Control.Arrow.StateListArrow

Methods

zeroArrow :: SLA s b c #

ArrowPlus (SLA s) Source # 
Instance details

Defined in Control.Arrow.StateListArrow

Methods

(<+>) :: SLA s b c -> SLA s b c -> SLA s b c #

ArrowChoice (SLA s) Source # 
Instance details

Defined in Control.Arrow.StateListArrow

Methods

left :: SLA s b c -> SLA s (Either b d) (Either c d) #

right :: SLA s b c -> SLA s (Either d b) (Either d c) #

(+++) :: SLA s b c -> SLA s b' c' -> SLA s (Either b b') (Either c c') #

(|||) :: SLA s b d -> SLA s c d -> SLA s (Either b c) d #

ArrowApply (SLA s) Source # 
Instance details

Defined in Control.Arrow.StateListArrow

Methods

app :: SLA s (SLA s b c, b) c #

ArrowList (SLA s) Source # 
Instance details

Defined in Control.Arrow.StateListArrow

Methods

arr2 :: (b1 -> b2 -> c) -> SLA s (b1, b2) c Source #

arr3 :: (b1 -> b2 -> b3 -> c) -> SLA s (b1, (b2, b3)) c Source #

arr4 :: (b1 -> b2 -> b3 -> b4 -> c) -> SLA s (b1, (b2, (b3, b4))) c Source #

arr2A :: (b -> SLA s c d) -> SLA s (b, c) d Source #

arrL :: (b -> [c]) -> SLA s b c Source #

arr2L :: (b -> c -> [d]) -> SLA s (b, c) d Source #

constA :: c -> SLA s b c Source #

constL :: [c] -> SLA s b c Source #

isA :: (b -> Bool) -> SLA s b b Source #

(>>.) :: SLA s b c -> ([c] -> [d]) -> SLA s b d Source #

(>.) :: SLA s b c -> ([c] -> d) -> SLA s b d Source #

listA :: SLA s b c -> SLA s b [c] Source #

unlistA :: SLA s [b] b Source #

this :: SLA s b b Source #

none :: SLA s b c Source #

withDefault :: SLA s b c -> c -> SLA s b c Source #

single :: SLA s b c -> SLA s b c Source #

applyA :: SLA s b (SLA s b c) -> SLA s b c Source #

($<) :: (c -> SLA s b d) -> SLA s b c -> SLA s b d Source #

($<<) :: (c1 -> c2 -> SLA s b d) -> SLA s b (c1, c2) -> SLA s b d Source #

($<<<) :: (c1 -> c2 -> c3 -> SLA s b d) -> SLA s b (c1, (c2, c3)) -> SLA s b d Source #

($<<<<) :: (c1 -> c2 -> c3 -> c4 -> SLA s b d) -> SLA s b (c1, (c2, (c3, c4))) -> SLA s b d Source #

($<$) :: (c -> SLA s b b) -> SLA s b c -> SLA s b b Source #

mergeA :: (SLA s (a1, b1) a1 -> SLA s (a1, b1) b1 -> SLA s (a1, b1) c) -> SLA s (a1, b1) c Source #

perform :: SLA s b c -> SLA s b b Source #

catA :: [SLA s b c] -> SLA s b c Source #

seqA :: [SLA s b b] -> SLA s b b Source #

ArrowIf (SLA s) Source # 
Instance details

Defined in Control.Arrow.StateListArrow

Methods

ifA :: SLA s b c -> SLA s b d -> SLA s b d -> SLA s b d Source #

ifP :: (b -> Bool) -> SLA s b d -> SLA s b d -> SLA s b d Source #

neg :: SLA s b c -> SLA s b b Source #

when :: SLA s b b -> SLA s b c -> SLA s b b Source #

whenP :: SLA s b b -> (b -> Bool) -> SLA s b b Source #

whenNot :: SLA s b b -> SLA s b c -> SLA s b b Source #

whenNotP :: SLA s b b -> (b -> Bool) -> SLA s b b Source #

guards :: SLA s b c -> SLA s b d -> SLA s b d Source #

guardsP :: (b -> Bool) -> SLA s b d -> SLA s b d Source #

filterA :: SLA s b c -> SLA s b b Source #

containing :: SLA s b c -> SLA s c d -> SLA s b c Source #

notContaining :: SLA s b c -> SLA s c d -> SLA s b c Source #

orElse :: SLA s b c -> SLA s b c -> SLA s b c Source #

choiceA :: [IfThen (SLA s b c) (SLA s b d)] -> SLA s b d Source #

tagA :: SLA s b c -> SLA s b (Either b b) Source #

spanA :: SLA s b b -> SLA s [b] ([b], [b]) Source #

partitionA :: SLA s b b -> SLA s [b] ([b], [b]) Source #

ArrowWNF (SLA s) Source # 
Instance details

Defined in Control.Arrow.StateListArrow

Methods

rwnfA :: WNFData c => SLA s b c -> SLA s b c Source #

rwnf2A :: WNFData c => SLA s b c -> SLA s b c Source #

ArrowNF (SLA s) Source # 
Instance details

Defined in Control.Arrow.StateListArrow

Methods

rnfA :: NFData c => SLA s b c -> SLA s b c Source #

ArrowTree (SLA s) Source # 
Instance details

Defined in Control.Arrow.StateListArrow

Methods

mkLeaf :: Tree t => b -> SLA s c (t b) Source #

mkTree :: Tree t => b -> [t b] -> SLA s c (t b) Source #

getChildren :: Tree t => SLA s (t b) (t b) Source #

getNode :: Tree t => SLA s (t b) b Source #

hasNode :: Tree t => (b -> Bool) -> SLA s (t b) (t b) Source #

setChildren :: Tree t => [t b] -> SLA s (t b) (t b) Source #

setNode :: Tree t => b -> SLA s (t b) (t b) Source #

changeChildren :: Tree t => ([t b] -> [t b]) -> SLA s (t b) (t b) Source #

changeNode :: Tree t => (b -> b) -> SLA s (t b) (t b) Source #

processChildren :: Tree t => SLA s (t b) (t b) -> SLA s (t b) (t b) Source #

replaceChildren :: Tree t => SLA s (t b) (t b) -> SLA s (t b) (t b) Source #

(/>) :: Tree t => SLA s b (t c) -> SLA s (t c) d -> SLA s b d Source #

(//>) :: Tree t => SLA s b (t c) -> SLA s (t c) d -> SLA s b d Source #

(</) :: Tree t => SLA s (t b) (t b) -> SLA s (t b) (t b) -> SLA s (t b) (t b) Source #

deep :: Tree t => SLA s (t b) c -> SLA s (t b) c Source #

deepest :: Tree t => SLA s (t b) c -> SLA s (t b) c Source #

multi :: Tree t => SLA s (t b) c -> SLA s (t b) c Source #

processBottomUp :: Tree t => SLA s (t b) (t b) -> SLA s (t b) (t b) Source #

processTopDown :: Tree t => SLA s (t b) (t b) -> SLA s (t b) (t b) Source #

processBottomUpWhenNot :: Tree t => SLA s (t b) (t b) -> SLA s (t b) (t b) -> SLA s (t b) (t b) Source #

processTopDownUntil :: Tree t => SLA s (t b) (t b) -> SLA s (t b) (t b) Source #

insertChildrenAt :: Tree t => Int -> SLA s (t b) (t b) -> SLA s (t b) (t b) Source #

insertChildrenAfter :: Tree t => SLA s (t b) (t b) -> SLA s (t b) (t b) -> SLA s (t b) (t b) Source #

insertTreeTemplate :: Tree t => SLA s (t b) (t b) -> [IfThen (SLA s (t b) c) (SLA s (t b) (t b))] -> SLA s (t b) (t b) Source #

ArrowNavigatableTree (SLA s) Source # 
Instance details

Defined in Control.Arrow.StateListArrow

Methods

moveUp :: NavigatableTree t => SLA s (t b) (t b) Source #

moveDown :: NavigatableTree t => SLA s (t b) (t b) Source #

moveLeft :: NavigatableTree t => SLA s (t b) (t b) Source #

moveRight :: NavigatableTree t => SLA s (t b) (t b) Source #

ArrowDTD (SLA s) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.XmlArrow

ArrowXml (SLA s) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.XmlArrow

Methods

isText :: SLA s XmlTree XmlTree Source #

isBlob :: SLA s XmlTree XmlTree Source #

isCharRef :: SLA s XmlTree XmlTree Source #

isEntityRef :: SLA s XmlTree XmlTree Source #

isCmt :: SLA s XmlTree XmlTree Source #

isCdata :: SLA s XmlTree XmlTree Source #

isPi :: SLA s XmlTree XmlTree Source #

isXmlPi :: SLA s XmlTree XmlTree Source #

isElem :: SLA s XmlTree XmlTree Source #

isDTD :: SLA s XmlTree XmlTree Source #

isAttr :: SLA s XmlTree XmlTree Source #

isError :: SLA s XmlTree XmlTree Source #

isRoot :: SLA s XmlTree XmlTree Source #

hasText :: (String -> Bool) -> SLA s XmlTree XmlTree Source #

isWhiteSpace :: SLA s XmlTree XmlTree Source #

hasNameWith :: (QName -> Bool) -> SLA s XmlTree XmlTree Source #

hasQName :: QName -> SLA s XmlTree XmlTree Source #

hasName :: String -> SLA s XmlTree XmlTree Source #

hasLocalPart :: String -> SLA s XmlTree XmlTree Source #

hasNamePrefix :: String -> SLA s XmlTree XmlTree Source #

hasNamespaceUri :: String -> SLA s XmlTree XmlTree Source #

hasAttr :: String -> SLA s XmlTree XmlTree Source #

hasQAttr :: QName -> SLA s XmlTree XmlTree Source #

hasAttrValue :: String -> (String -> Bool) -> SLA s XmlTree XmlTree Source #

hasQAttrValue :: QName -> (String -> Bool) -> SLA s XmlTree XmlTree Source #

mkText :: SLA s String XmlTree Source #

mkBlob :: SLA s Blob XmlTree Source #

mkCharRef :: SLA s Int XmlTree Source #

mkEntityRef :: SLA s String XmlTree Source #

mkCmt :: SLA s String XmlTree Source #

mkCdata :: SLA s String XmlTree Source #

mkError :: Int -> SLA s String XmlTree Source #

mkElement :: QName -> SLA s n XmlTree -> SLA s n XmlTree -> SLA s n XmlTree Source #

mkAttr :: QName -> SLA s n XmlTree -> SLA s n XmlTree Source #

mkPi :: QName -> SLA s n XmlTree -> SLA s n XmlTree Source #

mkqelem :: QName -> [SLA s n XmlTree] -> [SLA s n XmlTree] -> SLA s n XmlTree Source #

mkelem :: String -> [SLA s n XmlTree] -> [SLA s n XmlTree] -> SLA s n XmlTree Source #

aelem :: String -> [SLA s n XmlTree] -> SLA s n XmlTree Source #

selem :: String -> [SLA s n XmlTree] -> SLA s n XmlTree Source #

eelem :: String -> SLA s n XmlTree Source #

root :: [SLA s n XmlTree] -> [SLA s n XmlTree] -> SLA s n XmlTree Source #

qattr :: QName -> SLA s n XmlTree -> SLA s n XmlTree Source #

attr :: String -> SLA s n XmlTree -> SLA s n XmlTree Source #

txt :: String -> SLA s n XmlTree Source #

blb :: Blob -> SLA s n XmlTree Source #

charRef :: Int -> SLA s n XmlTree Source #

entityRef :: String -> SLA s n XmlTree Source #

cmt :: String -> SLA s n XmlTree Source #

warn :: String -> SLA s n XmlTree Source #

err :: String -> SLA s n XmlTree Source #

fatal :: String -> SLA s n XmlTree Source #

spi :: String -> String -> SLA s n XmlTree Source #

sqattr :: QName -> String -> SLA s n XmlTree Source #

sattr :: String -> String -> SLA s n XmlTree Source #

getText :: SLA s XmlTree String Source #

getCharRef :: SLA s XmlTree Int Source #

getEntityRef :: SLA s XmlTree String Source #

getCmt :: SLA s XmlTree String Source #

getCdata :: SLA s XmlTree String Source #

getPiName :: SLA s XmlTree QName Source #

getPiContent :: SLA s XmlTree XmlTree Source #

getElemName :: SLA s XmlTree QName Source #

getAttrl :: SLA s XmlTree XmlTree Source #

getDTDPart :: SLA s XmlTree DTDElem Source #

getDTDAttrl :: SLA s XmlTree Attributes Source #

getAttrName :: SLA s XmlTree QName Source #

getErrorLevel :: SLA s XmlTree Int Source #

getErrorMsg :: SLA s XmlTree String Source #

getQName :: SLA s XmlTree QName Source #

getName :: SLA s XmlTree String Source #

getUniversalName :: SLA s XmlTree String Source #

getUniversalUri :: SLA s XmlTree String Source #

getLocalPart :: SLA s XmlTree String Source #

getNamePrefix :: SLA s XmlTree String Source #

getNamespaceUri :: SLA s XmlTree String Source #

getAttrValue :: String -> SLA s XmlTree String Source #

getAttrValue0 :: String -> SLA s XmlTree String Source #

getQAttrValue :: QName -> SLA s XmlTree String Source #

getQAttrValue0 :: QName -> SLA s XmlTree String Source #

changeText :: (String -> String) -> SLA s XmlTree XmlTree Source #

changeBlob :: (Blob -> Blob) -> SLA s XmlTree XmlTree Source #

changeCmt :: (String -> String) -> SLA s XmlTree XmlTree Source #

changeQName :: (QName -> QName) -> SLA s XmlTree XmlTree Source #

changeElemName :: (QName -> QName) -> SLA s XmlTree XmlTree Source #

changeAttrName :: (QName -> QName) -> SLA s XmlTree XmlTree Source #

changePiName :: (QName -> QName) -> SLA s XmlTree XmlTree Source #

changeAttrValue :: (String -> String) -> SLA s XmlTree XmlTree Source #

changeAttrl :: (XmlTrees -> XmlTrees -> XmlTrees) -> SLA s XmlTree XmlTree -> SLA s XmlTree XmlTree Source #

setQName :: QName -> SLA s XmlTree XmlTree Source #

setElemName :: QName -> SLA s XmlTree XmlTree Source #

setAttrName :: QName -> SLA s XmlTree XmlTree Source #

setPiName :: QName -> SLA s XmlTree XmlTree Source #

setAttrl :: SLA s XmlTree XmlTree -> SLA s XmlTree XmlTree Source #

addAttrl :: SLA s XmlTree XmlTree -> SLA s XmlTree XmlTree Source #

addAttr :: String -> String -> SLA s XmlTree XmlTree Source #

removeAttr :: String -> SLA s XmlTree XmlTree Source #

removeQAttr :: QName -> SLA s XmlTree XmlTree Source #

processAttrl :: SLA s XmlTree XmlTree -> SLA s XmlTree XmlTree Source #

processTopDownWithAttrl :: SLA s XmlTree XmlTree -> SLA s XmlTree XmlTree Source #

(+=) :: SLA s b XmlTree -> SLA s b XmlTree -> SLA s b XmlTree Source #

xshow :: SLA s n XmlTree -> SLA s n String Source #

xshowBlob :: SLA s n XmlTree -> SLA s n Blob Source #

Category (SLA s :: Type -> Type -> Type) Source # 
Instance details

Defined in Control.Arrow.StateListArrow

Methods

id :: SLA s a a #

(.) :: SLA s b c -> SLA s a b -> SLA s a c #

fromSLA :: ArrowList a => s -> SLA s b c -> a b c Source #

conversion of state list arrows into arbitray other list arrows.

allows running a state list arrow within another arrow:

example:

... >>> fromSLA 0 (... setState ... getState ... ) >>> ...

runs a state arrow with initial state 0 (e..g. an Int) within another arrow sequence