HaXml-1.25.5: Utilities for manipulating XML documents

Safe HaskellSafe
LanguageHaskell98

Text.XML.HaXml.TypeMapping

Contents

Synopsis

A class to get an explicit type representation for any value

class HTypeable a where Source #

HTypeable promises that we can create an explicit representation of of the type of any value.

Methods

toHType :: a -> HType Source #

Instances
HTypeable Bool Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: Bool -> HType Source #

HTypeable Char Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: Char -> HType Source #

HTypeable Double Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: Double -> HType Source #

HTypeable Float Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: Float -> HType Source #

HTypeable Int Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: Int -> HType Source #

HTypeable Integer Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

HTypeable () Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: () -> HType Source #

HTypeable ANYContent Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

HTypeable a => HTypeable [a] Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: [a] -> HType Source #

HTypeable a => HTypeable (Maybe a) Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: Maybe a -> HType Source #

HTypeable a => HTypeable (List1 a) Source # 
Instance details

Defined in Text.XML.HaXml.XmlContent.Parser

Methods

toHType :: List1 a -> HType Source #

HTypeable a => HTypeable (OneOf1 a) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf1 a -> HType Source #

(HTypeable a, HTypeable b) => HTypeable (Either a b) Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: Either a b -> HType Source #

(HTypeable a, HTypeable b) => HTypeable (a, b) Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: (a, b) -> HType Source #

(HTypeable a, HTypeable b) => HTypeable (OneOf2 a b) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf2 a b -> HType Source #

(HTypeable a, HTypeable b, HTypeable c) => HTypeable (a, b, c) Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: (a, b, c) -> HType Source #

(HTypeable a, HTypeable b, HTypeable c) => HTypeable (OneOf3 a b c) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf3 a b c -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d) => HTypeable (a, b, c, d) Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: (a, b, c, d) -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d) => HTypeable (OneOf4 a b c d) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf4 a b c d -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e) => HTypeable (a, b, c, d, e) Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: (a, b, c, d, e) -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e) => HTypeable (OneOf5 a b c d e) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf5 a b c d e -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f) => HTypeable (a, b, c, d, e, f) Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: (a, b, c, d, e, f) -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f) => HTypeable (OneOf6 a b c d e f) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf6 a b c d e f -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g) => HTypeable (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: (a, b, c, d, e, f, g) -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g) => HTypeable (OneOf7 a b c d e f g) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf7 a b c d e f g -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h) => HTypeable (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: (a, b, c, d, e, f, g, h) -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h) => HTypeable (OneOf8 a b c d e f g h) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf8 a b c d e f g h -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h, HTypeable i) => HTypeable (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: (a, b, c, d, e, f, g, h, i) -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h, HTypeable i) => HTypeable (OneOf9 a b c d e f g h i) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf9 a b c d e f g h i -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h, HTypeable i, HTypeable j) => HTypeable (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: (a, b, c, d, e, f, g, h, i, j) -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h, HTypeable i, HTypeable j) => HTypeable (OneOf10 a b c d e f g h i j) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf10 a b c d e f g h i j -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h, HTypeable i, HTypeable j, HTypeable k) => HTypeable (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: (a, b, c, d, e, f, g, h, i, j, k) -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h, HTypeable i, HTypeable j, HTypeable k) => HTypeable (OneOf11 a b c d e f g h i j k) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf11 a b c d e f g h i j k -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h, HTypeable i, HTypeable j, HTypeable k, HTypeable l) => HTypeable (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: (a, b, c, d, e, f, g, h, i, j, k, l) -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h, HTypeable i, HTypeable j, HTypeable k, HTypeable l) => HTypeable (OneOf12 a b c d e f g h i j k l) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf12 a b c d e f g h i j k l -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h, HTypeable i, HTypeable j, HTypeable k, HTypeable l, HTypeable m) => HTypeable (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h, HTypeable i, HTypeable j, HTypeable k, HTypeable l, HTypeable m) => HTypeable (OneOf13 a b c d e f g h i j k l m) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf13 a b c d e f g h i j k l m -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h, HTypeable i, HTypeable j, HTypeable k, HTypeable l, HTypeable m, HTypeable n) => HTypeable (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h, HTypeable i, HTypeable j, HTypeable k, HTypeable l, HTypeable m, HTypeable n) => HTypeable (OneOf14 a b c d e f g h i j k l m n) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf14 a b c d e f g h i j k l m n -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h, HTypeable i, HTypeable j, HTypeable k, HTypeable l, HTypeable m, HTypeable n, HTypeable o) => HTypeable (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

toHType :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h, HTypeable i, HTypeable j, HTypeable k, HTypeable l, HTypeable m, HTypeable n, HTypeable o) => HTypeable (OneOf15 a b c d e f g h i j k l m n o) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf15 a b c d e f g h i j k l m n o -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h, HTypeable i, HTypeable j, HTypeable k, HTypeable l, HTypeable m, HTypeable n, HTypeable o, HTypeable p) => HTypeable (OneOf16 a b c d e f g h i j k l m n o p) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf16 a b c d e f g h i j k l m n o p -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h, HTypeable i, HTypeable j, HTypeable k, HTypeable l, HTypeable m, HTypeable n, HTypeable o, HTypeable p, HTypeable q) => HTypeable (OneOf17 a b c d e f g h i j k l m n o p q) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf17 a b c d e f g h i j k l m n o p q -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h, HTypeable i, HTypeable j, HTypeable k, HTypeable l, HTypeable m, HTypeable n, HTypeable o, HTypeable p, HTypeable q, HTypeable r) => HTypeable (OneOf18 a b c d e f g h i j k l m n o p q r) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf18 a b c d e f g h i j k l m n o p q r -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h, HTypeable i, HTypeable j, HTypeable k, HTypeable l, HTypeable m, HTypeable n, HTypeable o, HTypeable p, HTypeable q, HTypeable r, HTypeable s) => HTypeable (OneOf19 a b c d e f g h i j k l m n o p q r s) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf19 a b c d e f g h i j k l m n o p q r s -> HType Source #

(HTypeable a, HTypeable b, HTypeable c, HTypeable d, HTypeable e, HTypeable f, HTypeable g, HTypeable h, HTypeable i, HTypeable j, HTypeable k, HTypeable l, HTypeable m, HTypeable n, HTypeable o, HTypeable p, HTypeable q, HTypeable r, HTypeable s, HTypeable t) => HTypeable (OneOf20 a b c d e f g h i j k l m n o p q r s t) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf20 a b c d e f g h i j k l m n o p q r s t -> HType Source #

Explicit representation of Haskell datatype information

data HType Source #

A concrete representation of any Haskell type.

Constructors

Maybe HType 
List HType 
Tuple [HType] 
Prim String String

separate Haskell name and XML name

String 
Defined String [HType] [Constr]

A user-defined type has a name, a sequence of type variables, and a set of constructors. (The variables might already be instantiated to actual types.)

Instances
Eq HType Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

(==) :: HType -> HType -> Bool #

(/=) :: HType -> HType -> Bool #

Show HType Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

showsPrec :: Int -> HType -> ShowS #

show :: HType -> String #

showList :: [HType] -> ShowS #

data Constr Source #

A concrete representation of any user-defined Haskell constructor. The constructor has a name, and a sequence of component types. The first sequence of types represents the minimum set of free type variables occurring in the (second) list of real component types. If there are fieldnames, they are contained in the final list, and correspond one-to-one with the component types.

Constructors

Constr String [HType] [HType] 
Instances
Eq Constr Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Methods

(==) :: Constr -> Constr -> Bool #

(/=) :: Constr -> Constr -> Bool #

Show Constr Source # 
Instance details

Defined in Text.XML.HaXml.TypeMapping

Helper functions to extract type info as strings

showConstr :: Int -> HType -> String Source #

Project the n'th constructor from an HType and convert it to a string suitable for an XML tagname.

Conversion from Haskell datatype to DTD

toDTD :: HType -> DocTypeDecl Source #

toDTD converts a concrete representation of the Haskell type of a value (obtained by the method toHType) into a real DocTypeDecl. It ensures that PERefs are defined before they are used, and that no element or attribute-list is declared more than once.