happstack-data-0.5.0.3: Happstack data manipulation libraries

Happstack.Data.Xml

Synopsis

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.

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.

Instances

class (Data XmlD a, Default a, Normalize a) => Xml a whereSource

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[ahQe], Xml a[ahQf]) => Xml (Either a[ahQe] a[ahQf]) 
(Xml a[ahRT], Xml a[ahRU]) => Xml (a[ahRT], a[ahRU]) 
(Xml a[ahSP], Xml a[ahSQ], Xml a[ahSR]) => Xml (a[ahSP], a[ahSQ], a[ahSR]) 
(Xml a[ahTQ], Xml a[ahTR], Xml a[ahTS], Xml a[ahTT]) => Xml (a[ahTQ], a[ahTR], a[ahTS], a[ahTT]) 

data XmlD a Source

Constructors

XmlD 

Fields

toXmlD :: a -> [Element]
 
readMXmlD :: forall m. Monad m => Rigidity m -> ReadM m a
 
readMXmlNoRootDefaultD :: forall m. Monad m => Rigidity m -> ReadM Maybe a
 

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

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.

data ReadState Source

Constructors

ReadState 

Fields

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.

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 

Instances

Data K 
Read K 
Show K 
Typeable K 
Default K 
(Data ctx String, Sat (ctx K), Sat (ctx String)) => Data ctx K 

data W Source

Constructors

W [K] 

Instances

Data W 
Read W 
Show W 
Typeable W 
Default W 
(Data ctx [K], Sat (ctx W), Sat (ctx [K])) => Data ctx W 

class ToString a whereSource

Methods

toString :: a -> StringSource

Instances

class FromString a whereSource

Methods

fromString :: Monad m => Rigidity m -> String -> m aSource