Portability | portable |
---|---|
Stability | stable |
Maintainer | Uwe Schmidt (uwe@fh-wedel.de) |
Safe Haskell | None |
the basic state arrows for XML processing
A state is needed for global processing options, like encoding options, document base URI, trace levels and error message handling
The state is separated into a user defined state and a system state. The system state contains variables for error message handling, for tracing, for the document base for accessing XML documents with relative references, e.g. DTDs, and a global key value store. This assoc list has strings as keys and lists of XmlTrees as values. It is used to store arbitrary XML and text values, e.g. user defined global options.
The user defined part of the store is in the default case empty, defined as (). It can be extended with an arbitray data type
- data XIOState us = XIOState {
- xioSysState :: !XIOSysState
- xioUserState :: !us
- type IOStateArrow s b c = IOSLA (XIOState s) b c
- type IOSArrow b c = IOStateArrow () b c
- getUserState :: IOStateArrow s b s
- changeUserState :: (b -> s -> s) -> IOStateArrow s b b
- setUserState :: IOStateArrow s s s
- withExtendedUserState :: s1 -> IOStateArrow (s1, s0) b c -> IOStateArrow s0 b c
- withOtherUserState :: s1 -> IOStateArrow s1 b c -> IOStateArrow s0 b c
- withoutUserState :: IOSArrow b c -> IOStateArrow s0 b c
- data XIOSysState = XIOSys {}
- data XIOSysWriter = XIOwrt {
- xioErrorStatus :: !Int
- xioErrorMsgList :: !XmlTrees
- xioExpatErrors :: IOSArrow XmlTree XmlTree
- xioRelaxNoOfErrors :: !Int
- xioRelaxDefineId :: !Int
- xioRelaxAttrList :: AssocList String XmlTrees
- data XIOSysEnv = XIOEnv {
- xioTraceLevel :: !Int
- xioTraceCmd :: Int -> String -> IO ()
- xioErrorMsgHandler :: String -> IO ()
- xioErrorMsgCollect :: !Bool
- xioBaseURI :: !String
- xioDefaultBaseURI :: !String
- xioAttrList :: !Attributes
- xioInputConfig :: !XIOInputConfig
- xioParseConfig :: !XIOParseConfig
- xioOutputConfig :: !XIOOutputConfig
- xioRelaxConfig :: !XIORelaxConfig
- xioXmlSchemaConfig :: !XIOXmlSchemaConfig
- xioCacheConfig :: !XIOCacheConfig
- data XIOInputConfig = XIOIcgf {
- xioStrictInput :: !Bool
- xioEncodingErrors :: !Bool
- xioInputEncoding :: String
- xioHttpHandler :: IOSArrow XmlTree XmlTree
- xioInputOptions :: !Attributes
- xioRedirect :: !Bool
- xioProxy :: String
- data XIOParseConfig = XIOPcfg {
- xioMimeTypes :: MimeTypeTable
- xioMimeTypeHandlers :: MimeTypeHandlers
- xioMimeTypeFile :: String
- xioAcceptedMimeTypes :: [String]
- xioFileMimeType :: String
- xioWarnings :: !Bool
- xioRemoveWS :: !Bool
- xioParseByMimeType :: !Bool
- xioParseHTML :: !Bool
- xioLowerCaseNames :: !Bool
- xioPreserveComment :: !Bool
- xioValidate :: !Bool
- xioSubstDTDEntities :: !Bool
- xioSubstHTMLEntities :: !Bool
- xioCheckNamespaces :: !Bool
- xioCanonicalize :: !Bool
- xioIgnoreNoneXmlContents :: !Bool
- xioTagSoup :: !Bool
- xioTagSoupParser :: IOSArrow XmlTree XmlTree
- xioExpat :: !Bool
- xioExpatParser :: IOSArrow XmlTree XmlTree
- data XIOOutputConfig = XIOOcfg {
- xioIndent :: !Bool
- xioOutputEncoding :: !String
- xioOutputFmt :: !XIOXoutConfig
- xioXmlPi :: !Bool
- xioNoEmptyElemFor :: ![String]
- xioAddDefaultDTD :: !Bool
- xioTextMode :: !Bool
- xioShowTree :: !Bool
- xioShowHaskell :: !Bool
- data XIOXoutConfig
- = XMLoutput
- | XHTMLoutput
- | HTMLoutput
- | PLAINoutput
- data XIORelaxConfig = XIORxc {
- xioRelaxValidate :: !Bool
- xioRelaxSchema :: String
- xioRelaxCheckRestr :: !Bool
- xioRelaxValidateExtRef :: !Bool
- xioRelaxValidateInclude :: !Bool
- xioRelaxCollectErrors :: !Bool
- xioRelaxValidator :: IOSArrow XmlTree XmlTree
- data XIOXmlSchemaConfig = XIOScc {
- xioXmlSchemaValidate :: !Bool
- xioXmlSchemaSchema :: String
- xioXmlSchemaValidator :: IOSArrow XmlTree XmlTree
- data XIOCacheConfig = XIOCch {
- xioBinaryCompression :: CompressionFct
- xioBinaryDeCompression :: DeCompressionFct
- xioWithCache :: !Bool
- xioCacheDir :: !String
- xioDocumentAge :: !Int
- xioCache404Err :: !Bool
- xioCacheRead :: String -> IOSArrow XmlTree XmlTree
- xioStrictDeserialize :: !Bool
- type MimeTypeHandlers = Map String (IOSArrow XmlTree XmlTree)
- type CompressionFct = ByteString -> ByteString
- type DeCompressionFct = ByteString -> ByteString
- type SysConfig = XIOSysState -> XIOSysState
- type SysConfigList = [SysConfig]
- theSysState :: Selector (XIOState us) XIOSysState
- theUserState :: Selector (XIOState us) us
- theSysWriter :: Selector XIOSysState XIOSysWriter
- theErrorStatus :: Selector XIOSysState Int
- theErrorMsgList :: Selector XIOSysState XmlTrees
- theRelaxNoOfErrors :: Selector XIOSysState Int
- theRelaxDefineId :: Selector XIOSysState Int
- theRelaxAttrList :: Selector XIOSysState (AssocList String XmlTrees)
- theSysEnv :: Selector XIOSysState XIOSysEnv
- theInputConfig :: Selector XIOSysState XIOInputConfig
- theStrictInput :: Selector XIOSysState Bool
- theEncodingErrors :: Selector XIOSysState Bool
- theInputEncoding :: Selector XIOSysState String
- theHttpHandler :: Selector XIOSysState (IOSArrow XmlTree XmlTree)
- theInputOptions :: Selector XIOSysState Attributes
- theRedirect :: Selector XIOSysState Bool
- theProxy :: Selector XIOSysState String
- theOutputConfig :: Selector XIOSysState XIOOutputConfig
- theIndent :: Selector XIOSysState Bool
- theOutputEncoding :: Selector XIOSysState String
- theOutputFmt :: Selector XIOSysState XIOXoutConfig
- theXmlPi :: Selector XIOSysState Bool
- theNoEmptyElemFor :: Selector XIOSysState [String]
- theAddDefaultDTD :: Selector XIOSysState Bool
- theTextMode :: Selector XIOSysState Bool
- theShowTree :: Selector XIOSysState Bool
- theShowHaskell :: Selector XIOSysState Bool
- theRelaxConfig :: Selector XIOSysState XIORelaxConfig
- theRelaxValidate :: Selector XIOSysState Bool
- theRelaxSchema :: Selector XIOSysState String
- theRelaxCheckRestr :: Selector XIOSysState Bool
- theRelaxValidateExtRef :: Selector XIOSysState Bool
- theRelaxValidateInclude :: Selector XIOSysState Bool
- theRelaxCollectErrors :: Selector XIOSysState Bool
- theRelaxValidator :: Selector XIOSysState (IOSArrow XmlTree XmlTree)
- theXmlSchemaConfig :: Selector XIOSysState XIOXmlSchemaConfig
- theXmlSchemaValidate :: Selector XIOSysState Bool
- theXmlSchemaSchema :: Selector XIOSysState String
- theXmlSchemaValidator :: Selector XIOSysState (IOSArrow XmlTree XmlTree)
- theParseConfig :: Selector XIOSysState XIOParseConfig
- theErrorMsgHandler :: Selector XIOSysState (String -> IO ())
- theErrorMsgCollect :: Selector XIOSysState Bool
- theBaseURI :: Selector XIOSysState String
- theDefaultBaseURI :: Selector XIOSysState String
- theTraceLevel :: Selector XIOSysState Int
- theTraceCmd :: Selector XIOSysState (Int -> String -> IO ())
- theTrace :: Selector XIOSysState (Int, Int -> String -> IO ())
- theAttrList :: Selector XIOSysState Attributes
- theMimeTypes :: Selector XIOSysState MimeTypeTable
- theMimeTypeHandlers :: Selector XIOSysState MimeTypeHandlers
- theMimeTypeFile :: Selector XIOSysState String
- theAcceptedMimeTypes :: Selector XIOSysState [String]
- theFileMimeType :: Selector XIOSysState String
- theWarnings :: Selector XIOSysState Bool
- theRemoveWS :: Selector XIOSysState Bool
- thePreserveComment :: Selector XIOSysState Bool
- theParseByMimeType :: Selector XIOSysState Bool
- theParseHTML :: Selector XIOSysState Bool
- theLowerCaseNames :: Selector XIOSysState Bool
- theValidate :: Selector XIOSysState Bool
- theSubstDTDEntities :: Selector XIOSysState Bool
- theSubstHTMLEntities :: Selector XIOSysState Bool
- theCheckNamespaces :: Selector XIOSysState Bool
- theCanonicalize :: Selector XIOSysState Bool
- theIgnoreNoneXmlContents :: Selector XIOSysState Bool
- theTagSoup :: Selector XIOSysState Bool
- theTagSoupParser :: Selector XIOSysState (IOSArrow XmlTree XmlTree)
- theExpat :: Selector XIOSysState Bool
- theExpatParser :: Selector XIOSysState (IOSArrow XmlTree XmlTree)
- theExpatErrors :: Selector XIOSysState (IOSArrow XmlTree XmlTree)
- theCacheConfig :: Selector XIOSysState XIOCacheConfig
- theBinaryCompression :: Selector XIOSysState (ByteString -> ByteString)
- theBinaryDeCompression :: Selector XIOSysState (ByteString -> ByteString)
- theWithCache :: Selector XIOSysState Bool
- theCacheDir :: Selector XIOSysState String
- theDocumentAge :: Selector XIOSysState Int
- theCache404Err :: Selector XIOSysState Bool
- theCacheRead :: Selector XIOSysState (String -> IOSArrow XmlTree XmlTree)
- theStrictDeserialize :: Selector XIOSysState Bool
- getSysVar :: Selector XIOSysState c -> IOStateArrow s b c
- setSysVar :: Selector XIOSysState c -> IOStateArrow s c c
- chgSysVar :: Selector XIOSysState c -> (b -> c -> c) -> IOStateArrow s b b
- configSysVar :: SysConfig -> IOStateArrow s c c
- configSysVars :: SysConfigList -> IOStateArrow s c c
- localSysVar :: Selector XIOSysState c -> IOStateArrow s a b -> IOStateArrow s a b
- localSysEnv :: IOStateArrow s a b -> IOStateArrow s a b
- incrSysVar :: Selector XIOSysState Int -> IOStateArrow s a Int
- setSysAttr :: String -> IOStateArrow s String String
- unsetSysAttr :: String -> IOStateArrow s b b
- getSysAttr :: String -> IOStateArrow s b String
- getAllSysAttrs :: IOStateArrow s b Attributes
- setSysAttrString :: String -> String -> IOStateArrow s b b
- setSysAttrInt :: String -> Int -> IOStateArrow s b b
- getSysAttrInt :: Int -> String -> IOStateArrow s b Int
- toInt :: Int -> String -> Int
- data Selector s a = S {}
- chgS :: Selector s a -> (a -> a) -> s -> s
- idS :: Selector s s
- (.&&&.) :: Selector s a -> Selector s b -> Selector s (a, b)
Documentation
state datatype consists of a system state and a user state the user state is not fixed
XIOState | |
|
NFData us => NFData (XIOState us) |
type IOStateArrow s b c = IOSLA (XIOState s) b cSource
The arrow type for stateful arrows
type IOSArrow b c = IOStateArrow () b cSource
The arrow for stateful arrows with no user defined state
getUserState :: IOStateArrow s b sSource
read the user defined part of the state
changeUserState :: (b -> s -> s) -> IOStateArrow s b bSource
change the user defined part of the state
setUserState :: IOStateArrow s s sSource
set the user defined part of the state
withExtendedUserState :: s1 -> IOStateArrow (s1, s0) b c -> IOStateArrow s0 b cSource
extend user state
Run an arrow with an extended user state component, The old component is stored together with a new one in a pair, the arrow is executed with this extended state, and the augmented state component is removed form the state when the arrow has finished its execution
withOtherUserState :: s1 -> IOStateArrow s1 b c -> IOStateArrow s0 b cSource
change the type of user state
This conversion is useful, when running a state arrow with another structure of the user state, e.g. with () when executing some IO arrows
withoutUserState :: IOSArrow b c -> IOStateArrow s0 b cSource
data XIOSysState Source
predefined system state data type with all components for the system functions, like trace, error handling, ...
XIOSys | |
|
NFData XIOSysState |
data XIOSysWriter Source
XIOwrt | |
|
XIOEnv | |
|
data XIOInputConfig Source
XIOIcgf | |
|
data XIOParseConfig Source
XIOPcfg | |
|
data XIOOutputConfig Source
XIOOcfg | |
|
data XIORelaxConfig Source
XIORxc | |
|
data XIOXmlSchemaConfig Source
XIOScc | |
|
data XIOCacheConfig Source
XIOCch | |
|
type MimeTypeHandlers = Map String (IOSArrow XmlTree XmlTree)Source
type CompressionFct = ByteString -> ByteStringSource
type DeCompressionFct = ByteString -> ByteStringSource
type SysConfig = XIOSysState -> XIOSysStateSource
type SysConfigList = [SysConfig]Source
theSysState :: Selector (XIOState us) XIOSysStateSource
theUserState :: Selector (XIOState us) usSource
theRelaxAttrList :: Selector XIOSysState (AssocList String XmlTrees)Source
theStrictInput :: Selector XIOSysState BoolSource
theInputEncoding :: Selector XIOSysState StringSource
theRedirect :: Selector XIOSysState BoolSource
theProxy :: Selector XIOSysState StringSource
theIndent :: Selector XIOSysState BoolSource
theOutputEncoding :: Selector XIOSysState StringSource
theXmlPi :: Selector XIOSysState BoolSource
theNoEmptyElemFor :: Selector XIOSysState [String]Source
theTextMode :: Selector XIOSysState BoolSource
theShowTree :: Selector XIOSysState BoolSource
theShowHaskell :: Selector XIOSysState BoolSource
theRelaxSchema :: Selector XIOSysState StringSource
theXmlSchemaSchema :: Selector XIOSysState StringSource
theErrorMsgHandler :: Selector XIOSysState (String -> IO ())Source
theBaseURI :: Selector XIOSysState StringSource
theDefaultBaseURI :: Selector XIOSysState StringSource
theTraceCmd :: Selector XIOSysState (Int -> String -> IO ())Source
theTrace :: Selector XIOSysState (Int, Int -> String -> IO ())Source
theMimeTypeFile :: Selector XIOSysState StringSource
theAcceptedMimeTypes :: Selector XIOSysState [String]Source
theFileMimeType :: Selector XIOSysState StringSource
theWarnings :: Selector XIOSysState BoolSource
theRemoveWS :: Selector XIOSysState BoolSource
theParseHTML :: Selector XIOSysState BoolSource
theValidate :: Selector XIOSysState BoolSource
theCanonicalize :: Selector XIOSysState BoolSource
theTagSoup :: Selector XIOSysState BoolSource
theExpat :: Selector XIOSysState BoolSource
theBinaryCompression :: Selector XIOSysState (ByteString -> ByteString)Source
theBinaryDeCompression :: Selector XIOSysState (ByteString -> ByteString)Source
theWithCache :: Selector XIOSysState BoolSource
theCacheDir :: Selector XIOSysState StringSource
theCache404Err :: Selector XIOSysState BoolSource
theCacheRead :: Selector XIOSysState (String -> IOSArrow XmlTree XmlTree)Source
getSysVar :: Selector XIOSysState c -> IOStateArrow s b cSource
setSysVar :: Selector XIOSysState c -> IOStateArrow s c cSource
chgSysVar :: Selector XIOSysState c -> (b -> c -> c) -> IOStateArrow s b bSource
configSysVar :: SysConfig -> IOStateArrow s c cSource
configSysVars :: SysConfigList -> IOStateArrow s c cSource
localSysVar :: Selector XIOSysState c -> IOStateArrow s a b -> IOStateArrow s a bSource
localSysEnv :: IOStateArrow s a b -> IOStateArrow s a bSource
incrSysVar :: Selector XIOSysState Int -> IOStateArrow s a IntSource
setSysAttr :: String -> IOStateArrow s String StringSource
store a string in global state under a given attribute name
unsetSysAttr :: String -> IOStateArrow s b bSource
remove an entry in global state, arrow input remains unchanged
getSysAttr :: String -> IOStateArrow s b StringSource
read an attribute value from global state
getAllSysAttrs :: IOStateArrow s b AttributesSource
read all attributes from global state
setSysAttrString :: String -> String -> IOStateArrow s b bSource
setSysAttrInt :: String -> Int -> IOStateArrow s b bSource
store an int value in global state
getSysAttrInt :: Int -> String -> IOStateArrow s b IntSource
read an int value from global state
getSysAttrInt 0 myIntAttr
A Selector is a pair of an access function and a modifying function for reading and updating parts of a composite type
Category Selector |