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

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

Control.Arrow.IOListArrow

Description

Implementation of pure list arrows with IO

Synopsis

Documentation

newtype IOLA a b Source #

list arrow combined with IO monad

Constructors

IOLA 

Fields

Instances
Arrow IOLA Source # 
Instance details

Defined in Control.Arrow.IOListArrow

Methods

arr :: (b -> c) -> IOLA b c #

first :: IOLA b c -> IOLA (b, d) (c, d) #

second :: IOLA b c -> IOLA (d, b) (d, c) #

(***) :: IOLA b c -> IOLA b' c' -> IOLA (b, b') (c, c') #

(&&&) :: IOLA b c -> IOLA b c' -> IOLA b (c, c') #

ArrowZero IOLA Source # 
Instance details

Defined in Control.Arrow.IOListArrow

Methods

zeroArrow :: IOLA b c #

ArrowPlus IOLA Source # 
Instance details

Defined in Control.Arrow.IOListArrow

Methods

(<+>) :: IOLA b c -> IOLA b c -> IOLA b c #

ArrowChoice IOLA Source # 
Instance details

Defined in Control.Arrow.IOListArrow

Methods

left :: IOLA b c -> IOLA (Either b d) (Either c d) #

right :: IOLA b c -> IOLA (Either d b) (Either d c) #

(+++) :: IOLA b c -> IOLA b' c' -> IOLA (Either b b') (Either c c') #

(|||) :: IOLA b d -> IOLA c d -> IOLA (Either b c) d #

ArrowApply IOLA Source # 
Instance details

Defined in Control.Arrow.IOListArrow

Methods

app :: IOLA (IOLA b c, b) c #

ArrowIOIf IOLA Source # 
Instance details

Defined in Control.Arrow.IOListArrow

Methods

isIOA :: (b -> IO Bool) -> IOLA b b Source #

ArrowIO IOLA Source # 
Instance details

Defined in Control.Arrow.IOListArrow

Methods

arrIO :: (b -> IO c) -> IOLA b c Source #

arrIO0 :: IO c -> IOLA b c Source #

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

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

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

ArrowExc IOLA Source # 
Instance details

Defined in Control.Arrow.IOListArrow

Methods

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

catchA :: IOLA b c -> IOLA SomeException c -> IOLA b c Source #

ArrowList IOLA Source # 
Instance details

Defined in Control.Arrow.IOListArrow

Methods

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

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

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

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

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

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

constA :: c -> IOLA b c Source #

constL :: [c] -> IOLA b c Source #

isA :: (b -> Bool) -> IOLA b b Source #

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

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

listA :: IOLA b c -> IOLA b [c] Source #

unlistA :: IOLA [b] b Source #

this :: IOLA b b Source #

none :: IOLA b c Source #

withDefault :: IOLA b c -> c -> IOLA b c Source #

single :: IOLA b c -> IOLA b c Source #

applyA :: IOLA b (IOLA b c) -> IOLA b c Source #

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

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

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

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

($<$) :: (c -> IOLA b b) -> IOLA b c -> IOLA b b Source #

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

perform :: IOLA b c -> IOLA b b Source #

catA :: [IOLA b c] -> IOLA b c Source #

seqA :: [IOLA b b] -> IOLA b b Source #

ArrowIf IOLA Source # 
Instance details

Defined in Control.Arrow.IOListArrow

Methods

ifA :: IOLA b c -> IOLA b d -> IOLA b d -> IOLA b d Source #

ifP :: (b -> Bool) -> IOLA b d -> IOLA b d -> IOLA b d Source #

neg :: IOLA b c -> IOLA b b Source #

when :: IOLA b b -> IOLA b c -> IOLA b b Source #

whenP :: IOLA b b -> (b -> Bool) -> IOLA b b Source #

whenNot :: IOLA b b -> IOLA b c -> IOLA b b Source #

whenNotP :: IOLA b b -> (b -> Bool) -> IOLA b b Source #

guards :: IOLA b c -> IOLA b d -> IOLA b d Source #

guardsP :: (b -> Bool) -> IOLA b d -> IOLA b d Source #

filterA :: IOLA b c -> IOLA b b Source #

containing :: IOLA b c -> IOLA c d -> IOLA b c Source #

notContaining :: IOLA b c -> IOLA c d -> IOLA b c Source #

orElse :: IOLA b c -> IOLA b c -> IOLA b c Source #

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

tagA :: IOLA b c -> IOLA b (Either b b) Source #

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

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

ArrowWNF IOLA Source # 
Instance details

Defined in Control.Arrow.IOListArrow

Methods

rwnfA :: WNFData c => IOLA b c -> IOLA b c Source #

rwnf2A :: WNFData c => IOLA b c -> IOLA b c Source #

ArrowNF IOLA Source # 
Instance details

Defined in Control.Arrow.IOListArrow

Methods

rnfA :: NFData c => IOLA b c -> IOLA b c Source #

ArrowTree IOLA Source # 
Instance details

Defined in Control.Arrow.IOListArrow

Methods

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

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

getChildren :: Tree t => IOLA (t b) (t b) Source #

getNode :: Tree t => IOLA (t b) b Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

ArrowNavigatableTree IOLA Source # 
Instance details

Defined in Control.Arrow.IOListArrow

Methods

moveUp :: NavigatableTree t => IOLA (t b) (t b) Source #

moveDown :: NavigatableTree t => IOLA (t b) (t b) Source #

moveLeft :: NavigatableTree t => IOLA (t b) (t b) Source #

moveRight :: NavigatableTree t => IOLA (t b) (t b) Source #

ArrowDTD IOLA Source # 
Instance details

Defined in Text.XML.HXT.Arrow.XmlArrow

ArrowXml IOLA Source # 
Instance details

Defined in Text.XML.HXT.Arrow.XmlArrow

Methods

isText :: IOLA XmlTree XmlTree Source #

isBlob :: IOLA XmlTree XmlTree Source #

isCharRef :: IOLA XmlTree XmlTree Source #

isEntityRef :: IOLA XmlTree XmlTree Source #

isCmt :: IOLA XmlTree XmlTree Source #

isCdata :: IOLA XmlTree XmlTree Source #

isPi :: IOLA XmlTree XmlTree Source #

isXmlPi :: IOLA XmlTree XmlTree Source #

isElem :: IOLA XmlTree XmlTree Source #

isDTD :: IOLA XmlTree XmlTree Source #

isAttr :: IOLA XmlTree XmlTree Source #

isError :: IOLA XmlTree XmlTree Source #

isRoot :: IOLA XmlTree XmlTree Source #

hasText :: (String -> Bool) -> IOLA XmlTree XmlTree Source #

isWhiteSpace :: IOLA XmlTree XmlTree Source #

hasNameWith :: (QName -> Bool) -> IOLA XmlTree XmlTree Source #

hasQName :: QName -> IOLA XmlTree XmlTree Source #

hasName :: String -> IOLA XmlTree XmlTree Source #

hasLocalPart :: String -> IOLA XmlTree XmlTree Source #

hasNamePrefix :: String -> IOLA XmlTree XmlTree Source #

hasNamespaceUri :: String -> IOLA XmlTree XmlTree Source #

hasAttr :: String -> IOLA XmlTree XmlTree Source #

hasQAttr :: QName -> IOLA XmlTree XmlTree Source #

hasAttrValue :: String -> (String -> Bool) -> IOLA XmlTree XmlTree Source #

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

mkText :: IOLA String XmlTree Source #

mkBlob :: IOLA Blob XmlTree Source #

mkCharRef :: IOLA Int XmlTree Source #

mkEntityRef :: IOLA String XmlTree Source #

mkCmt :: IOLA String XmlTree Source #

mkCdata :: IOLA String XmlTree Source #

mkError :: Int -> IOLA String XmlTree Source #

mkElement :: QName -> IOLA n XmlTree -> IOLA n XmlTree -> IOLA n XmlTree Source #

mkAttr :: QName -> IOLA n XmlTree -> IOLA n XmlTree Source #

mkPi :: QName -> IOLA n XmlTree -> IOLA n XmlTree Source #

mkqelem :: QName -> [IOLA n XmlTree] -> [IOLA n XmlTree] -> IOLA n XmlTree Source #

mkelem :: String -> [IOLA n XmlTree] -> [IOLA n XmlTree] -> IOLA n XmlTree Source #

aelem :: String -> [IOLA n XmlTree] -> IOLA n XmlTree Source #

selem :: String -> [IOLA n XmlTree] -> IOLA n XmlTree Source #

eelem :: String -> IOLA n XmlTree Source #

root :: [IOLA n XmlTree] -> [IOLA n XmlTree] -> IOLA n XmlTree Source #

qattr :: QName -> IOLA n XmlTree -> IOLA n XmlTree Source #

attr :: String -> IOLA n XmlTree -> IOLA n XmlTree Source #

txt :: String -> IOLA n XmlTree Source #

blb :: Blob -> IOLA n XmlTree Source #

charRef :: Int -> IOLA n XmlTree Source #

entityRef :: String -> IOLA n XmlTree Source #

cmt :: String -> IOLA n XmlTree Source #

warn :: String -> IOLA n XmlTree Source #

err :: String -> IOLA n XmlTree Source #

fatal :: String -> IOLA n XmlTree Source #

spi :: String -> String -> IOLA n XmlTree Source #

sqattr :: QName -> String -> IOLA n XmlTree Source #

sattr :: String -> String -> IOLA n XmlTree Source #

getText :: IOLA XmlTree String Source #

getCharRef :: IOLA XmlTree Int Source #

getEntityRef :: IOLA XmlTree String Source #

getCmt :: IOLA XmlTree String Source #

getCdata :: IOLA XmlTree String Source #

getPiName :: IOLA XmlTree QName Source #

getPiContent :: IOLA XmlTree XmlTree Source #

getElemName :: IOLA XmlTree QName Source #

getAttrl :: IOLA XmlTree XmlTree Source #

getDTDPart :: IOLA XmlTree DTDElem Source #

getDTDAttrl :: IOLA XmlTree Attributes Source #

getAttrName :: IOLA XmlTree QName Source #

getErrorLevel :: IOLA XmlTree Int Source #

getErrorMsg :: IOLA XmlTree String Source #

getQName :: IOLA XmlTree QName Source #

getName :: IOLA XmlTree String Source #

getUniversalName :: IOLA XmlTree String Source #

getUniversalUri :: IOLA XmlTree String Source #

getLocalPart :: IOLA XmlTree String Source #

getNamePrefix :: IOLA XmlTree String Source #

getNamespaceUri :: IOLA XmlTree String Source #

getAttrValue :: String -> IOLA XmlTree String Source #

getAttrValue0 :: String -> IOLA XmlTree String Source #

getQAttrValue :: QName -> IOLA XmlTree String Source #

getQAttrValue0 :: QName -> IOLA XmlTree String Source #

changeText :: (String -> String) -> IOLA XmlTree XmlTree Source #

changeBlob :: (Blob -> Blob) -> IOLA XmlTree XmlTree Source #

changeCmt :: (String -> String) -> IOLA XmlTree XmlTree Source #

changeQName :: (QName -> QName) -> IOLA XmlTree XmlTree Source #

changeElemName :: (QName -> QName) -> IOLA XmlTree XmlTree Source #

changeAttrName :: (QName -> QName) -> IOLA XmlTree XmlTree Source #

changePiName :: (QName -> QName) -> IOLA XmlTree XmlTree Source #

changeAttrValue :: (String -> String) -> IOLA XmlTree XmlTree Source #

changeAttrl :: (XmlTrees -> XmlTrees -> XmlTrees) -> IOLA XmlTree XmlTree -> IOLA XmlTree XmlTree Source #

setQName :: QName -> IOLA XmlTree XmlTree Source #

setElemName :: QName -> IOLA XmlTree XmlTree Source #

setAttrName :: QName -> IOLA XmlTree XmlTree Source #

setPiName :: QName -> IOLA XmlTree XmlTree Source #

setAttrl :: IOLA XmlTree XmlTree -> IOLA XmlTree XmlTree Source #

addAttrl :: IOLA XmlTree XmlTree -> IOLA XmlTree XmlTree Source #

addAttr :: String -> String -> IOLA XmlTree XmlTree Source #

removeAttr :: String -> IOLA XmlTree XmlTree Source #

removeQAttr :: QName -> IOLA XmlTree XmlTree Source #

processAttrl :: IOLA XmlTree XmlTree -> IOLA XmlTree XmlTree Source #

processTopDownWithAttrl :: IOLA XmlTree XmlTree -> IOLA XmlTree XmlTree Source #

(+=) :: IOLA b XmlTree -> IOLA b XmlTree -> IOLA b XmlTree Source #

xshow :: IOLA n XmlTree -> IOLA n String Source #

xshowBlob :: IOLA n XmlTree -> IOLA n Blob Source #

Category IOLA Source # 
Instance details

Defined in Control.Arrow.IOListArrow

Methods

id :: IOLA a a #

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