happstack-data-0.2.1: Happstack data manipulation librariesSource codeContentsIndex
Happstack.Data.Pairs
Synopsis
pairsToXml :: Pairs -> [Element]
xmlToPairs :: [Element] -> Pairs
pairsToHTMLForm :: String -> String -> String -> Pairs -> [Element]
xmlToHTMLForm :: (Xml a, Show a, Data a, Eq a) => String -> String -> String -> a -> [Element]
toPairsX :: (Xml a, Show a, Data a, Eq a) => a -> Pairs
toHTMLForm :: (Xml a, Show a, Data a, Eq a) => String -> String -> String -> a -> [Element]
type Pairs = [(String, String)]
class (Xml x, Show x, Data x) => AsPairs x where
toPairs :: x -> Pairs
fromPairs :: Pairs -> Maybe x
Documentation
pairsToXml :: Pairs -> [Element]Source
Converts lists of string pairs into a list of Elements. The basic structure is pairsToXml [(foo,bar)] = [Elem foo [CData bar]] pairsToXml [(foo/bar,baz)] = [Elem foo [Elem bar [CData baz]]]
xmlToPairs :: [Element] -> PairsSource
Converts a list of Elements to a list of String pairs. xmlToPairs [CData _] = error xmlToPairs [Elem foo [CData bar]] = [(foo,bar)] xmlToPairs [Elem foo [Elem bar [CData baz]]] = [(foo/bar,baz)] xmlToPairs . pairsToXml = id
pairsToHTMLForm :: String -> String -> String -> Pairs -> [Element]Source
Creates the Xml structure corresponding to the specification of an HTML form. The provided pairs should be the spec of the inputs to the form.
xmlToHTMLForm :: (Xml a, Show a, Data a, Eq a) => String -> String -> String -> a -> [Element]Source
Equivalent to pairsToHTMLForm but first converts the Xml instance to list of pairs.
toPairsX :: (Xml a, Show a, Data a, Eq a) => a -> PairsSource
toHTMLForm :: (Xml a, Show a, Data a, Eq a) => String -> String -> String -> a -> [Element]Source
Equivalent to pairsToHTMLForm but first converts the Xml instance to list of pairs. An alias for xmlToHTMLForm currently.
type Pairs = [(String, String)]Source
class (Xml x, Show x, Data x) => AsPairs x whereSource
Methods
toPairs :: x -> PairsSource
fromPairs :: Pairs -> Maybe xSource
Produced by Haddock version 2.4.2