HAppS-Data-0.9.3: HAppS data manipulation librariesSource codeContentsIndex
HAppS.Data.Xml
Documentation
data Element Source
Constructors
Elem String [Element]
CData String
Attr String String
show/hide Instances
dataType[a63M] :: DataTypeSource
constr[a63P] :: ConstrSource
constr[a63O] :: ConstrSource
constr[a63N] :: ConstrSource
fromXml :: forall m a. (Monad m, Xml a) => Rigidity m -> [Element] -> m aSource
data Other b Source
Constructors
forall a . (Migrate a b, Xml a) => Other a
NoOther
toPublicXml :: Xml a => a -> [Element]Source
data Rigidity m whereSource
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 ()
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[abA3], Xml a[abA4]) => Xml (Either a[abA3] a[abA4])
(Xml a[abEy], Xml a[abEz]) => Xml ((,) a[abEy] a[abEz])
(Xml a, Xml b) => Xml (Couple a b)
(Xml a[abHO], Xml a[abHP], Xml a[abHQ]) => Xml ((,,) a[abHO] a[abHP] a[abHQ])
(Xml a[abLY], Xml a[abLZ], Xml a[abM0], Xml a[abM1]) => Xml ((,,,) a[abLY] a[abLZ] a[abM0] a[abM1])
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
first :: (a -> a) -> [a] -> [a]Source
defaultToXml :: Xml t => t -> [Element]Source
transparentToXml :: Xml t => t -> [Element]Source
transparentReadXml :: forall m t. (Monad m, Xml t) => Rigidity m -> [Element] -> Maybe ([Element], t)Source
transparentXml :: Name -> Q [Dec]Source
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
getAttr :: String -> [Element] -> Maybe (String, [Element])Source
versionAttr :: StringSource
typeAttr :: StringSource
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
constrFromElementsNoRootDefault :: forall m t. (Monad m, Xml t) => Rigidity m -> Constr -> [Element] -> Maybe ([Element], t)Source
constrFromElements :: forall m t. (Monad m, Xml t) => Rigidity m -> Constr -> [Element] -> m ([Element], t)Source
type ReadM m = StateT ReadState mSource
data ReadState Source
Constructors
ReadState
xmls :: [Element]
getXmls :: Monad m => ReadM m [Element]Source
putXmls :: Monad m => [Element] -> ReadM m ()Source
readMXml :: (Monad m, Xml a) => Rigidity m -> ReadM m aSource
readMXmlNoRootDefault :: (Monad m, Xml a) => Rigidity m -> ReadM Maybe aSource
xmlAttr :: Name -> Q [Dec]Source
xmlShowCDatas :: [Name] -> Q [Dec]Source
xmlShowCData :: Name -> Q [Dec]Source
xmlCDataLists :: [Name] -> Q [Dec]Source
xmlCDataList :: Name -> Q [Dec]Source
noCommas :: String -> StringSource
typeNotValue :: Xml a => a -> aSource
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[adTk] :: DataTypeSource
constr[adTl] :: ConstrSource
dataType[adTa] :: DataTypeSource
constr[adTb] :: 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.4.2