Copyright | (c) Uwe Schmidt Andrea Rossato |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Andrea Rossato <andrea.rossato@unitn.it> |
Stability | unstable |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
This module is mostly copied from Text.XML.HXT.Arrow.Pickle.Xml which is an adaptation of the pickler combinators developed by Andrew Kennedy.
See: http://research.microsoft.com/~akenn/fun/picklercombinators.pdf
- data St = St {
- attributes :: [Attr]
- contents :: [Content]
- data PU a = PU {}
- pickleXML :: PU a -> a -> String
- unpickleXML :: PU a -> [Content] -> Maybe a
- emptySt :: St
- addAtt :: Attr -> St -> St
- addCont :: Content -> St -> St
- dropCont :: St -> St
- getAtt :: String -> St -> Maybe Attr
- getCont :: St -> Maybe Content
- class XmlPickler a where
- xpPrim :: (Read a, Show a) => PU a
- xpUnit :: PU ()
- xpZero :: PU a
- xpLift :: a -> PU a
- xpCondSeq :: PU b -> (b -> a) -> PU a -> (a -> PU b) -> PU b
- xpSeq :: (b -> a) -> PU a -> (a -> PU b) -> PU b
- xpChoice :: PU b -> PU a -> (a -> PU b) -> PU b
- xpWrap :: (a -> b, b -> a) -> PU a -> PU b
- xpDefault :: Eq a => a -> PU a -> PU a
- xpOption :: PU a -> PU (Maybe a)
- xpAlt :: (a -> Int) -> [PU a] -> PU a
- xpList :: PU a -> PU [a]
- xpLiftMaybe :: Maybe a -> PU a
- xpWrapMaybe :: (a -> Maybe b, b -> a) -> PU a -> PU b
- xpPair :: PU a -> PU b -> PU (a, b)
- xpTriple :: PU a -> PU b -> PU c -> PU (a, b, c)
- xp4Tuple :: PU a -> PU b -> PU c -> PU d -> PU (a, b, c, d)
- xp5Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU (a, b, c, d, e)
- xp6Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU (a, b, c, d, e, f)
- xpText :: PU String
- xpText0 :: PU String
- xpElem :: String -> PU a -> PU a
- xpIElem :: String -> PU a -> PU a
- xpAttr :: String -> PU a -> PU a
- xpElemWithAttrValue :: String -> String -> String -> PU a -> PU a
- xpAttrFixed :: String -> String -> PU ()
- xpAddFixedAttr :: String -> String -> PU a -> PU a
- uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d
- uncurry4 :: (a -> b -> c -> d -> e) -> (a, b, c, d) -> e
- uncurry5 :: (a -> b -> c -> d -> e -> f) -> (a, b, c, d, e) -> f
- unescape :: String -> String
- readXmlString :: Show a => PU a -> ByteString -> a
- readXmlFile :: Show a => PU a -> FilePath -> IO a
- readFile' :: FilePath -> IO ByteString
Documentation
unpickleXML :: PU a -> [Content] -> Maybe a Source
class XmlPickler a where Source
xpLiftMaybe :: Maybe a -> PU a Source
xpWrapMaybe :: (a -> Maybe b, b -> a) -> PU a -> PU b Source
xpAttrFixed :: String -> String -> PU () Source
readXmlString :: Show a => PU a -> ByteString -> a Source
readFile' :: FilePath -> IO ByteString Source