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

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

Control.Arrow.IOStateListArrow

Description

Implementation of arrows with IO and a state

Synopsis

Documentation

newtype IOSLA s a b Source #

list arrow combined with a state and the IO monad

Constructors

IOSLA 

Fields

Instances

ArrowState s (IOSLA s) Source # 

Methods

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

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

getState :: IOSLA s b s Source #

setState :: IOSLA s s s Source #

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

Arrow (IOSLA s) Source # 

Methods

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

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

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

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

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

ArrowZero (IOSLA s) Source # 

Methods

zeroArrow :: IOSLA s b c #

ArrowPlus (IOSLA s) Source # 

Methods

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

ArrowChoice (IOSLA s) Source # 

Methods

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

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

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

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

ArrowApply (IOSLA s) Source # 

Methods

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

ArrowList (IOSLA s) Source # 

Methods

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

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

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

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

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

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

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

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

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

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

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

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

unlistA :: IOSLA s [b] b Source #

this :: IOSLA s b b Source #

none :: IOSLA s b c Source #

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

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

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

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

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

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

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

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

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

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

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

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

ArrowWNF (IOSLA s) Source # 

Methods

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

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

ArrowNF (IOSLA s) Source # 

Methods

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

ArrowIf (IOSLA s) Source # 

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

ArrowNavigatableTree (IOSLA s) Source # 

Methods

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

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

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

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

ArrowTree (IOSLA s) Source # 

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

ArrowIOIf (IOSLA s) Source # 

Methods

isIOA :: (b -> IO Bool) -> IOSLA s b b Source #

ArrowIO (IOSLA s) Source # 

Methods

arrIO :: (b -> IO c) -> IOSLA s b c Source #

arrIO0 :: IO c -> IOSLA s b c Source #

arrIO2 :: (b1 -> b2 -> IO c) -> IOSLA s (b1, b2) c Source #

arrIO3 :: (b1 -> b2 -> b3 -> IO c) -> IOSLA s (b1, (b2, b3)) c Source #

arrIO4 :: (b1 -> b2 -> b3 -> b4 -> IO c) -> IOSLA s (b1, (b2, (b3, b4))) c Source #

ArrowExc (IOSLA s) Source # 

Methods

tryA :: IOSLA s b c -> IOSLA s b (Either SomeException c) Source #

catchA :: IOSLA s b c -> IOSLA s SomeException c -> IOSLA s b c Source #

ArrowDTD (IOSLA s) Source # 
ArrowXml (IOSLA s) Source # 

Methods

isText :: IOSLA s XmlTree XmlTree Source #

isBlob :: IOSLA s XmlTree XmlTree Source #

isCharRef :: IOSLA s XmlTree XmlTree Source #

isEntityRef :: IOSLA s XmlTree XmlTree Source #

isCmt :: IOSLA s XmlTree XmlTree Source #

isCdata :: IOSLA s XmlTree XmlTree Source #

isPi :: IOSLA s XmlTree XmlTree Source #

isXmlPi :: IOSLA s XmlTree XmlTree Source #

isElem :: IOSLA s XmlTree XmlTree Source #

isDTD :: IOSLA s XmlTree XmlTree Source #

isAttr :: IOSLA s XmlTree XmlTree Source #

isError :: IOSLA s XmlTree XmlTree Source #

isRoot :: IOSLA s XmlTree XmlTree Source #

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

isWhiteSpace :: IOSLA s XmlTree XmlTree Source #

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

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

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

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

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

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

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

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

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

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

mkText :: IOSLA s String XmlTree Source #

mkBlob :: IOSLA s Blob XmlTree Source #

mkCharRef :: IOSLA s Int XmlTree Source #

mkEntityRef :: IOSLA s String XmlTree Source #

mkCmt :: IOSLA s String XmlTree Source #

mkCdata :: IOSLA s String XmlTree Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

getText :: IOSLA s XmlTree String Source #

getCharRef :: IOSLA s XmlTree Int Source #

getEntityRef :: IOSLA s XmlTree String Source #

getCmt :: IOSLA s XmlTree String Source #

getCdata :: IOSLA s XmlTree String Source #

getPiName :: IOSLA s XmlTree QName Source #

getPiContent :: IOSLA s XmlTree XmlTree Source #

getElemName :: IOSLA s XmlTree QName Source #

getAttrl :: IOSLA s XmlTree XmlTree Source #

getDTDPart :: IOSLA s XmlTree DTDElem Source #

getDTDAttrl :: IOSLA s XmlTree Attributes Source #

getAttrName :: IOSLA s XmlTree QName Source #

getErrorLevel :: IOSLA s XmlTree Int Source #

getErrorMsg :: IOSLA s XmlTree String Source #

getQName :: IOSLA s XmlTree QName Source #

getName :: IOSLA s XmlTree String Source #

getUniversalName :: IOSLA s XmlTree String Source #

getUniversalUri :: IOSLA s XmlTree String Source #

getLocalPart :: IOSLA s XmlTree String Source #

getNamePrefix :: IOSLA s XmlTree String Source #

getNamespaceUri :: IOSLA s XmlTree String Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Category * (IOSLA s) Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

liftSt :: IOSLA s1 b c -> IOSLA (s1, s2) b c Source #

lift the state of an IOSLA arrow to a state with an additional component.

This is uesful, when running predefined IO arrows, e.g. for document input, in a context with a more complex state component.

runSt :: s2 -> IOSLA (s1, s2) b c -> IOSLA s1 b c Source #

run an arrow with augmented state in the context of a simple state arrow. An initial value for the new state component is needed.

This is useful, when running an arrow with an extra environment component, e.g. for namespace handling in XML.