happstack-data-0.5.0: Happstack data manipulation librariesSource codeContentsIndex
Happstack.Data.Xml
Synopsis
data Element
= Elem String [Element]
| CData String
| Attr String String
dataType[a6S8] :: DataType
constr[a6Sb] :: Constr
constr[a6Sa] :: Constr
constr[a6S9] :: Constr
insEl :: (Data XmlD a, Default a, Data NormalizeD a, Data XmlD b, Default b, Data NormalizeD b) => a -> b -> Element
fromXml :: forall m a. (Monad m, Xml a) => Rigidity m -> [Element] -> m a
data Other b
= forall a . (Migrate a b, Xml a) => Other a
| NoOther
toPublicXml :: Xml a => a -> [Element]
data Rigidity m where
Rigid :: Rigidity Maybe
Flexible :: Rigidity Identity
class (Data XmlD a, Default a, Normalize a) => Xml a where
toXml :: a -> [Element]
readXml :: Monad m => Rigidity m -> [Element] -> Maybe ([Element], a)
readXml' :: Monad m => Rigidity m -> [Element] -> Maybe ([Element], a)
normalizeXml :: a -> [Element] -> [Element]
version :: a -> Maybe String
otherVersion :: a -> Other a
typ :: a -> String
data XmlD a = XmlD {
toXmlD :: a -> [Element]
readMXmlD :: forall m. Monad m => Rigidity m -> ReadM m a
readMXmlNoRootDefaultD :: forall m. Monad m => Rigidity m -> ReadM Maybe a
}
xmlProxy :: Proxy XmlD
first :: (a -> a) -> [a] -> [a]
defaultToXml :: Xml t => t -> [Element]
transparentToXml :: Xml t => t -> [Element]
transparentReadXml :: forall m t. (Monad m, Xml t) => Rigidity m -> [Element] -> Maybe ([Element], t)
transparentXml :: Name -> Q [Dec]
defaultReadXml :: (Monad m, Xml t) => Rigidity m -> [Element] -> Maybe ([Element], t)
defaultReadXml' :: (Monad m, Xml t) => Rigidity m -> [Element] -> Maybe ([Element], t)
readXmlWith :: Xml t => (Rigidity m -> Element -> Maybe t) -> Rigidity m -> [Element] -> Maybe ([Element], t)
readVersionedElement :: forall m t. (Monad m, Xml t) => Rigidity m -> Element -> Maybe t
isTheAttr :: String -> Element -> Bool
getAttr :: String -> [Element] -> Maybe (String, [Element])
versionAttr :: String
typeAttr :: String
readElement :: forall m t. (Monad m, Xml t) => Rigidity m -> Element -> Maybe t
aConstrFromElements :: forall m t. (Monad m, Xml t) => Rigidity m -> [Constr] -> [Element] -> Maybe ([Element], t)
constrFromElementsNoRootDefault :: forall m t. (Monad m, Xml t) => Rigidity m -> Constr -> [Element] -> Maybe ([Element], t)
constrFromElements :: forall m t. (Monad m, Xml t) => Rigidity m -> Constr -> [Element] -> m ([Element], t)
type ReadM m = StateT ReadState m
data ReadState = ReadState {
xmls :: [Element]
}
getXmls :: Monad m => ReadM m [Element]
putXmls :: Monad m => [Element] -> ReadM m ()
readMXml :: (Monad m, Xml a) => Rigidity m -> ReadM m a
readMXmlNoRootDefault :: (Monad m, Xml a) => Rigidity m -> ReadM Maybe a
xmlAttr :: Name -> Q [Dec]
xmlShowCDatas :: [Name] -> Q [Dec]
xmlShowCData :: Name -> Q [Dec]
xmlCDataLists :: [Name] -> Q [Dec]
xmlCDataList :: Name -> Q [Dec]
noCommas :: String -> String
typeNotValue :: Xml a => a -> a
data K = K String
data W = W [K]
dataType[afJG] :: DataType
constr[afJH] :: Constr
dataType[afJw] :: DataType
constr[afJx] :: Constr
class ToString a where
toString :: a -> String
class FromString a where
fromString :: Monad m => Rigidity m -> String -> m a
Documentation
data Element Source
Element recursively represents XML data. Elem n elems -> XML element with name n and described by elems. Note that elems contains sub-elements as well as the attributes or literal data of the element. CData d -> Literal string data Attr key val -> Key/Value pair of the element attribute.
Constructors
Elem String [Element]
CData String
Attr String String
show/hide Instances
dataType[a6S8] :: DataTypeSource
constr[a6Sb] :: ConstrSource
constr[a6Sa] :: ConstrSource
constr[a6S9] :: ConstrSource
insEl :: (Data XmlD a, Default a, Data NormalizeD a, Data XmlD b, Default b, Data NormalizeD b) => a -> b -> ElementSource
insEl a b will convert a to xml and insert it into the xml of b if b results in an Elem constructor.
fromXml :: forall m a. (Monad m, Xml a) => Rigidity m -> [Element] -> m aSource
Wrapper around the Xml class method readXml. The Rigidity will determine the behavior in the case of a failed parsing: Rigid will return Nothing and Flexible will return Identity (defaultValue)
data Other b Source
Constructors
forall a . (Migrate a b, Xml a) => Other a
NoOther
toPublicXml :: Xml a => a -> [Element]Source
Identical to toXml from Xml class except that it will remove attributes named haskellType or haskellTypeVersion
data Rigidity m whereSource
Rigidity is used to designate the result of a failed Xml parsing.
Constructors
Rigid :: Rigidity Maybe
Flexible :: Rigidity Identity
show/hide Instances
class (Data XmlD a, Default a, Normalize a) => Xml a whereSource
Methods
toXml :: a -> [Element]Source
readXml :: Monad m => Rigidity m -> [Element] -> Maybe ([Element], a)Source
readXml' :: Monad m => Rigidity m -> [Element] -> Maybe ([Element], a)Source
normalizeXml :: a -> [Element] -> [Element]Source
version :: a -> Maybe StringSource
otherVersion :: a -> Other aSource
typ :: a -> StringSource
show/hide Instances
Xml Bool
Xml Char
Xml Double
Xml Float
Xml Int
Xml Integer
Xml String
Xml ()
(Data XmlD t, Default t, Normalize t) => Xml t
Xml ByteString
Xml Element
Xml [Double]
Xml [Float]
Xml [Int]
Xml [Integer]
Xml [String]
(Xml a, Xml [a]) => Xml [a]
Xml a => Xml (Maybe a)
(Xml a[ahMb], Xml a[ahMc]) => Xml (Either a[ahMb] a[ahMc])
(Xml a[ahQF], Xml a[ahQG]) => Xml (a[ahQF], a[ahQG])
(Xml a[ahTU], Xml a[ahTV], Xml a[ahTW]) => Xml (a[ahTU], a[ahTV], a[ahTW])
(Xml a[ahY3], Xml a[ahY4], Xml a[ahY5], Xml a[ahY6]) => Xml (a[ahY3], a[ahY4], a[ahY5], a[ahY6])
data XmlD a Source
Constructors
XmlD
toXmlD :: a -> [Element]
readMXmlD :: forall m. Monad m => Rigidity m -> ReadM m a
readMXmlNoRootDefaultD :: forall m. Monad m => Rigidity m -> ReadM Maybe a
show/hide Instances
Xml t => Sat (XmlD t)
xmlProxy :: Proxy XmlDSource
Used as a type witness for usage with syb-with-class Data class.
first :: (a -> a) -> [a] -> [a]Source
Applies function to only first element of the list. Safe on empty lists.
defaultToXml :: Xml t => t -> [Element]Source
Converts the argument to an Xml element with the constructor name as the root of the Elem and the additional attributes corresponding to haskellType and haskellTypeVersion added
transparentToXml :: Xml t => t -> [Element]Source
Generically traverses an instance of Xml and converts it into a list of elements
transparentReadXml :: forall m t. (Monad m, Xml t) => Rigidity m -> [Element] -> Maybe ([Element], t)Source
Attempts to parse the set of elements and return the first constructor it can successfully parse of the inferred type.
transparentXml :: Name -> Q [Dec]Source
Create an Xml instance using transparentToXml and transparentReadXml
defaultReadXml :: (Monad m, Xml t) => Rigidity m -> [Element] -> Maybe ([Element], t)Source
defaultReadXml' :: (Monad m, Xml t) => Rigidity m -> [Element] -> Maybe ([Element], t)Source
readXmlWith :: Xml t => (Rigidity m -> Element -> Maybe t) -> Rigidity m -> [Element] -> Maybe ([Element], t)Source
readVersionedElement :: forall m t. (Monad m, Xml t) => Rigidity m -> Element -> Maybe tSource
isTheAttr :: String -> Element -> BoolSource
Matches the provided string to the key of an attribute. Returns False if any other Element constructor is given.
getAttr :: String -> [Element] -> Maybe (String, [Element])Source
Fetch the value of the given attribute if present, if not present will return Nothing
versionAttr :: StringSource
Attribute used for Xml class version information
typeAttr :: StringSource
Attribute used for recording the actual Haskell type in the xml serialization
readElement :: forall m t. (Monad m, Xml t) => Rigidity m -> Element -> Maybe tSource
aConstrFromElements :: forall m t. (Monad m, Xml t) => Rigidity m -> [Constr] -> [Element] -> Maybe ([Element], t)Source
aConstrFromElements will return the results of the first constructor that parses correctly.
constrFromElementsNoRootDefault :: forall m t. (Monad m, Xml t) => Rigidity m -> Constr -> [Element] -> Maybe ([Element], t)Source
Like constrFromElements but does not allow defaulting in case of a parse error.
constrFromElements :: forall m t. (Monad m, Xml t) => Rigidity m -> Constr -> [Element] -> m ([Element], t)Source
Attempts to parse the given elements to build the particular type given by the constructor argument.
type ReadM m = StateT ReadState mSource
data ReadState Source
Constructors
ReadState
xmls :: [Element]
getXmls :: Monad m => ReadM m [Element]Source
Returns the elements currently in the state
putXmls :: Monad m => [Element] -> ReadM m ()Source
Sets the state of the xml parsing to the given value
readMXml :: (Monad m, Xml a) => Rigidity m -> ReadM m aSource
Attempts to parse the current set of elements. If it fails the behavior is dependent on the Rigidity. If it is Rigid, then it will return Nothing but if it is Flexible it will return the defaultValue. If the parsing succeeds, it will return the value and store the remaining XML elements in the parser state.
readMXmlNoRootDefault :: (Monad m, Xml a) => Rigidity m -> ReadM Maybe aSource
Identical to readMXml except that in the case of a failed parsing it will not use defaultValue.
xmlAttr :: Name -> Q [Dec]Source
xmlShowCDatas :: [Name] -> Q [Dec]Source
xmlShowCData lifted to act on lists
xmlShowCData :: Name -> Q [Dec]Source
automatically creates an Xml definition for a type that is an instance of Show and Read. This will result in an instance that converts the type to and from CData.
xmlCDataLists :: [Name] -> Q [Dec]Source
xmlCDataLists lifted to act on lists
xmlCDataList :: Name -> Q [Dec]Source
Creates an instance similar to xmlShowCData except for lists of the provided type
noCommas :: String -> StringSource
Replaces commas in the string with single spaces
typeNotValue :: Xml a => a -> aSource
Throws an error when called
data K Source
Constructors
K String
show/hide Instances
data W Source
Constructors
W [K]
show/hide Instances
Data W
Read W
Show W
Typeable W
Default W
(Data ctx [K], Sat (ctx W), Sat (ctx [K])) => Data ctx W
dataType[afJG] :: DataTypeSource
constr[afJH] :: ConstrSource
dataType[afJw] :: DataTypeSource
constr[afJx] :: ConstrSource
class ToString a whereSource
Methods
toString :: a -> StringSource
show/hide Instances
class FromString a whereSource
Methods
fromString :: Monad m => Rigidity m -> String -> m aSource
show/hide Instances
Produced by Haddock version 2.6.1