HaXml-1.25.5: Utilities for manipulating XML documents

Safe HaskellNone
LanguageHaskell98

Text.XML.HaXml.OneOfN

Synopsis

Documentation

data OneOf1 a Source #

Somewhat of a nonsense - a choice of a single item. But sometimes it occurs in auto-generated code.

Constructors

OneOf1 a 
Instances
Eq a => Eq (OneOf1 a) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

(==) :: OneOf1 a -> OneOf1 a -> Bool #

(/=) :: OneOf1 a -> OneOf1 a -> Bool #

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

Defined in Text.XML.HaXml.OneOfN

Methods

showsPrec :: Int -> OneOf1 a -> ShowS #

show :: OneOf1 a -> String #

showList :: [OneOf1 a] -> ShowS #

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

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf1 a -> HType Source #

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

Defined in Text.XML.HaXml.OneOfN

foldOneOf1 :: (a -> z) -> OneOf1 a -> z Source #

data OneOf2 a b Source #

Equivalent to the Either type, but using the regular naming scheme of this module.

Constructors

OneOf2 a 
TwoOf2 b 
Instances
(Eq a, Eq b) => Eq (OneOf2 a b) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

(==) :: OneOf2 a b -> OneOf2 a b -> Bool #

(/=) :: OneOf2 a b -> OneOf2 a b -> Bool #

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

Defined in Text.XML.HaXml.OneOfN

Methods

showsPrec :: Int -> OneOf2 a b -> ShowS #

show :: OneOf2 a b -> String #

showList :: [OneOf2 a b] -> ShowS #

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

Defined in Text.XML.HaXml.OneOfN

Methods

toHType :: OneOf2 a b -> HType Source #

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

Defined in Text.XML.HaXml.OneOfN

foldOneOf2 :: (a -> z) -> (b -> z) -> OneOf2 a b -> z Source #

data OneOf3 a b c Source #

Constructors

OneOf3 a 
TwoOf3 b 
ThreeOf3 c 
Instances
(Eq a, Eq b, Eq c) => Eq (OneOf3 a b c) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

(==) :: OneOf3 a b c -> OneOf3 a b c -> Bool #

(/=) :: OneOf3 a b c -> OneOf3 a b c -> Bool #

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

Defined in Text.XML.HaXml.OneOfN

Methods

showsPrec :: Int -> OneOf3 a b c -> ShowS #

show :: OneOf3 a b c -> String #

showList :: [OneOf3 a b c] -> ShowS #

(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 #

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

Defined in Text.XML.HaXml.OneOfN

foldOneOf3 :: (a -> z) -> (b -> z) -> (c -> z) -> OneOf3 a b c -> z Source #

data OneOf4 a b c d Source #

Constructors

OneOf4 a 
TwoOf4 b 
ThreeOf4 c 
FourOf4 d 
Instances
(Eq a, Eq b, Eq c, Eq d) => Eq (OneOf4 a b c d) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

(==) :: OneOf4 a b c d -> OneOf4 a b c d -> Bool #

(/=) :: OneOf4 a b c d -> OneOf4 a b c d -> Bool #

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

Defined in Text.XML.HaXml.OneOfN

Methods

showsPrec :: Int -> OneOf4 a b c d -> ShowS #

show :: OneOf4 a b c d -> String #

showList :: [OneOf4 a b c d] -> ShowS #

(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 #

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

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf4 a b c d) Source #

toContents :: OneOf4 a b c d -> [Content ()] Source #

xToChar :: OneOf4 a b c d -> Char Source #

xFromChar :: Char -> OneOf4 a b c d Source #

foldOneOf4 :: (a -> z) -> (b -> z) -> (c -> z) -> (d -> z) -> OneOf4 a b c d -> z Source #

data OneOf5 a b c d e Source #

Constructors

OneOf5 a 
TwoOf5 b 
ThreeOf5 c 
FourOf5 d 
FiveOf5 e 
Instances
(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (OneOf5 a b c d e) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

(==) :: OneOf5 a b c d e -> OneOf5 a b c d e -> Bool #

(/=) :: OneOf5 a b c d e -> OneOf5 a b c d e -> Bool #

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

Defined in Text.XML.HaXml.OneOfN

Methods

showsPrec :: Int -> OneOf5 a b c d e -> ShowS #

show :: OneOf5 a b c d e -> String #

showList :: [OneOf5 a b c d e] -> ShowS #

(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 #

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

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf5 a b c d e) Source #

toContents :: OneOf5 a b c d e -> [Content ()] Source #

xToChar :: OneOf5 a b c d e -> Char Source #

xFromChar :: Char -> OneOf5 a b c d e Source #

foldOneOf5 :: (a -> z) -> (b -> z) -> (c -> z) -> (d -> z) -> (e -> z) -> OneOf5 a b c d e -> z Source #

data OneOf6 a b c d e f Source #

Constructors

OneOf6 a 
TwoOf6 b 
ThreeOf6 c 
FourOf6 d 
FiveOf6 e 
SixOf6 f 
Instances
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (OneOf6 a b c d e f) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

(==) :: OneOf6 a b c d e f -> OneOf6 a b c d e f -> Bool #

(/=) :: OneOf6 a b c d e f -> OneOf6 a b c d e f -> Bool #

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

Defined in Text.XML.HaXml.OneOfN

Methods

showsPrec :: Int -> OneOf6 a b c d e f -> ShowS #

show :: OneOf6 a b c d e f -> String #

showList :: [OneOf6 a b c d e f] -> ShowS #

(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 #

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

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf6 a b c d e f) Source #

toContents :: OneOf6 a b c d e f -> [Content ()] Source #

xToChar :: OneOf6 a b c d e f -> Char Source #

xFromChar :: Char -> OneOf6 a b c d e f Source #

foldOneOf6 :: (a -> z) -> (b -> z) -> (c -> z) -> (d -> z) -> (e -> z) -> (f -> z) -> OneOf6 a b c d e f -> z Source #

data OneOf7 a b c d e f g Source #

Constructors

OneOf7 a 
TwoOf7 b 
ThreeOf7 c 
FourOf7 d 
FiveOf7 e 
SixOf7 f 
SevenOf7 g 
Instances
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (OneOf7 a b c d e f g) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

(==) :: OneOf7 a b c d e f g -> OneOf7 a b c d e f g -> Bool #

(/=) :: OneOf7 a b c d e f g -> OneOf7 a b c d e f g -> Bool #

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

Defined in Text.XML.HaXml.OneOfN

Methods

showsPrec :: Int -> OneOf7 a b c d e f g -> ShowS #

show :: OneOf7 a b c d e f g -> String #

showList :: [OneOf7 a b c d e f g] -> ShowS #

(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 #

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

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf7 a b c d e f g) Source #

toContents :: OneOf7 a b c d e f g -> [Content ()] Source #

xToChar :: OneOf7 a b c d e f g -> Char Source #

xFromChar :: Char -> OneOf7 a b c d e f g Source #

foldOneOf7 :: (a -> z) -> (b -> z) -> (c -> z) -> (d -> z) -> (e -> z) -> (f -> z) -> (g -> z) -> OneOf7 a b c d e f g -> z Source #

data OneOf8 a b c d e f g h Source #

Constructors

OneOf8 a 
TwoOf8 b 
ThreeOf8 c 
FourOf8 d 
FiveOf8 e 
SixOf8 f 
SevenOf8 g 
EightOf8 h 
Instances
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h) => Eq (OneOf8 a b c d e f g h) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

(==) :: OneOf8 a b c d e f g h -> OneOf8 a b c d e f g h -> Bool #

(/=) :: OneOf8 a b c d e f g h -> OneOf8 a b c d e f g h -> Bool #

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

Defined in Text.XML.HaXml.OneOfN

Methods

showsPrec :: Int -> OneOf8 a b c d e f g h -> ShowS #

show :: OneOf8 a b c d e f g h -> String #

showList :: [OneOf8 a b c d e f g h] -> ShowS #

(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 #

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

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf8 a b c d e f g h) Source #

toContents :: OneOf8 a b c d e f g h -> [Content ()] Source #

xToChar :: OneOf8 a b c d e f g h -> Char Source #

xFromChar :: Char -> OneOf8 a b c d e f g h Source #

foldOneOf8 :: (a -> z) -> (b -> z) -> (c -> z) -> (d -> z) -> (e -> z) -> (f -> z) -> (g -> z) -> (h -> z) -> OneOf8 a b c d e f g h -> z Source #

data OneOf9 a b c d e f g h i Source #

Constructors

OneOf9 a 
TwoOf9 b 
ThreeOf9 c 
FourOf9 d 
FiveOf9 e 
SixOf9 f 
SevenOf9 g 
EightOf9 h 
NineOf9 i 
Instances
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) => Eq (OneOf9 a b c d e f g h i) Source # 
Instance details

Defined in Text.XML.HaXml.OneOfN

Methods

(==) :: OneOf9 a b c d e f g h i -> OneOf9 a b c d e f g h i -> Bool #

(/=) :: OneOf9 a b c d e f g h i -> OneOf9 a b c d e f g h i -> Bool #

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

Defined in Text.XML.HaXml.OneOfN

Methods

showsPrec :: Int -> OneOf9 a b c d e f g h i -> ShowS #

show :: OneOf9 a b c d e f g h i -> String #

showList :: [OneOf9 a b c d e f g h i] -> ShowS #

(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 #

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

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf9 a b c d e f g h i) Source #

toContents :: OneOf9 a b c d e f g h i -> [Content ()] Source #

xToChar :: OneOf9 a b c d e f g h i -> Char Source #

xFromChar :: Char -> OneOf9 a b c d e f g h i Source #

foldOneOf9 :: (a -> z) -> (b -> z) -> (c -> z) -> (d -> z) -> (e -> z) -> (f -> z) -> (g -> z) -> (h -> z) -> (i -> z) -> OneOf9 a b c d e f g h i -> z Source #

data OneOf10 a b c d e f g h i j Source #

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

Defined in Text.XML.HaXml.OneOfN

Methods

(==) :: OneOf10 a b c d e f g h i j -> OneOf10 a b c d e f g h i j -> Bool #

(/=) :: OneOf10 a b c d e f g h i j -> OneOf10 a b c d e f g h i j -> Bool #

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

Defined in Text.XML.HaXml.OneOfN

Methods

showsPrec :: Int -> OneOf10 a b c d e f g h i j -> ShowS #

show :: OneOf10 a b c d e f g h i j -> String #

showList :: [OneOf10 a b c d e f g h i j] -> ShowS #

(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 #

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

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf10 a b c d e f g h i j) Source #

toContents :: OneOf10 a b c d e f g h i j -> [Content ()] Source #

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

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

foldOneOf10 :: (a -> z) -> (b -> z) -> (c -> z) -> (d -> z) -> (e -> z) -> (f -> z) -> (g -> z) -> (h -> z) -> (i -> z) -> (j -> z) -> OneOf10 a b c d e f g h i j -> z Source #

data OneOf11 a b c d e f g h i j k Source #

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

Defined in Text.XML.HaXml.OneOfN

Methods

(==) :: OneOf11 a b c d e f g h i j k -> OneOf11 a b c d e f g h i j k -> Bool #

(/=) :: OneOf11 a b c d e f g h i j k -> OneOf11 a b c d e f g h i j k -> Bool #

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

Defined in Text.XML.HaXml.OneOfN

Methods

showsPrec :: Int -> OneOf11 a b c d e f g h i j k -> ShowS #

show :: OneOf11 a b c d e f g h i j k -> String #

showList :: [OneOf11 a b c d e f g h i j k] -> ShowS #

(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 #

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

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf11 a b c d e f g h i j k) Source #

toContents :: OneOf11 a b c d e f g h i j k -> [Content ()] Source #

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

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

foldOneOf11 :: (a -> z) -> (b -> z) -> (c -> z) -> (d -> z) -> (e -> z) -> (f -> z) -> (g -> z) -> (h -> z) -> (i -> z) -> (j -> z) -> (k -> z) -> OneOf11 a b c d e f g h i j k -> z Source #

data OneOf12 a b c d e f g h i j k l Source #

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

Defined in Text.XML.HaXml.OneOfN

Methods

(==) :: OneOf12 a b c d e f g h i j k l -> OneOf12 a b c d e f g h i j k l -> Bool #

(/=) :: OneOf12 a b c d e f g h i j k l -> OneOf12 a b c d e f g h i j k l -> Bool #

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

Defined in Text.XML.HaXml.OneOfN

Methods

showsPrec :: Int -> OneOf12 a b c d e f g h i j k l -> ShowS #

show :: OneOf12 a b c d e f g h i j k l -> String #

showList :: [OneOf12 a b c d e f g h i j k l] -> ShowS #

(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 #

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

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf12 a b c d e f g h i j k l) Source #

toContents :: OneOf12 a b c d e f g h i j k l -> [Content ()] Source #

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

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

foldOneOf12 :: (a -> z) -> (b -> z) -> (c -> z) -> (d -> z) -> (e -> z) -> (f -> z) -> (g -> z) -> (h -> z) -> (i -> z) -> (j -> z) -> (k -> z) -> (l -> z) -> OneOf12 a b c d e f g h i j k l -> z Source #

data OneOf13 a b c d e f g h i j k l m Source #

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

Defined in Text.XML.HaXml.OneOfN

Methods

(==) :: OneOf13 a b c d e f g h i j k l m -> OneOf13 a b c d e f g h i j k l m -> Bool #

(/=) :: OneOf13 a b c d e f g h i j k l m -> OneOf13 a b c d e f g h i j k l m -> Bool #

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

Defined in Text.XML.HaXml.OneOfN

Methods

showsPrec :: Int -> OneOf13 a b c d e f g h i j k l m -> ShowS #

show :: OneOf13 a b c d e f g h i j k l m -> String #

showList :: [OneOf13 a b c d e f g h i j k l m] -> ShowS #

(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 #

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

Defined in Text.XML.HaXml.OneOfN

Methods

parseContents :: XMLParser (OneOf13 a b c d e f g h i j k l m) Source #

toContents :: OneOf13 a b c d e f g h i j k l m -> [Content ()] Source #

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

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

foldOneOf13 :: (a -> z) -> (b -> z) -> (c -> z) -> (d -> z) -> (e -> z) -> (f -> z) -> (g -> z) -> (h -> z) -> (i -> z) -> (j -> z) -> (k -> z) -> (l -> z) -> (m -> z) -> OneOf13 a b c d e f g h i j k l m -> z Source #

data OneOf14 a b c d e f g h i j k l m n Source #

Instances
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n) => Eq (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

(==) :: OneOf14 a b c d e f g h i j k l m n -> OneOf14 a b c d e f g h i j k l m n -> Bool #

(/=) :: OneOf14 a b c d e f g h i j k l m n -> OneOf14 a b c d e f g h i j k l m n -> Bool #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n) => Show (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

showsPrec :: Int -> OneOf14 a b c d e f g h i j k l m n -> ShowS #

show :: OneOf14 a b c d e f g h i j k l m n -> String #

showList :: [OneOf14 a b c d e f g h i j k l m n] -> ShowS #

(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 #

(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i, XmlContent j, XmlContent k, XmlContent l, XmlContent m, XmlContent n) => XmlContent (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

parseContents :: XMLParser (OneOf14 a b c d e f g h i j k l m n) Source #

toContents :: OneOf14 a b c d e f g h i j k l m n -> [Content ()] Source #

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

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

foldOneOf14 :: (a -> z) -> (b -> z) -> (c -> z) -> (d -> z) -> (e -> z) -> (f -> z) -> (g -> z) -> (h -> z) -> (i -> z) -> (j -> z) -> (k -> z) -> (l -> z) -> (m -> z) -> (n -> z) -> OneOf14 a b c d e f g h i j k l m n -> z Source #

data OneOf15 a b c d e f g h i j k l m n o Source #

Instances
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o) => Eq (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

(==) :: OneOf15 a b c d e f g h i j k l m n o -> OneOf15 a b c d e f g h i j k l m n o -> Bool #

(/=) :: OneOf15 a b c d e f g h i j k l m n o -> OneOf15 a b c d e f g h i j k l m n o -> Bool #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n, Show o) => Show (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

showsPrec :: Int -> OneOf15 a b c d e f g h i j k l m n o -> ShowS #

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

showList :: [OneOf15 a b c d e f g h i j k l m n o] -> ShowS #

(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 #

(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i, XmlContent j, XmlContent k, XmlContent l, XmlContent m, XmlContent n, XmlContent o) => XmlContent (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

parseContents :: XMLParser (OneOf15 a b c d e f g h i j k l m n o) Source #

toContents :: OneOf15 a b c d e f g h i j k l m n o -> [Content ()] Source #

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

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

foldOneOf15 :: (a -> z) -> (b -> z) -> (c -> z) -> (d -> z) -> (e -> z) -> (f -> z) -> (g -> z) -> (h -> z) -> (i -> z) -> (j -> z) -> (k -> z) -> (l -> z) -> (m -> z) -> (n -> z) -> (o -> z) -> OneOf15 a b c d e f g h i j k l m n o -> z Source #

data OneOf16 a b c d e f g h i j k l m n o p Source #

Instances
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o, Eq p) => Eq (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

(==) :: OneOf16 a b c d e f g h i j k l m n o p -> OneOf16 a b c d e f g h i j k l m n o p -> Bool #

(/=) :: OneOf16 a b c d e f g h i j k l m n o p -> OneOf16 a b c d e f g h i j k l m n o p -> Bool #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n, Show o, Show p) => Show (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

showsPrec :: Int -> OneOf16 a b c d e f g h i j k l m n o p -> ShowS #

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

showList :: [OneOf16 a b c d e f g h i j k l m n o p] -> ShowS #

(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 #

(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i, XmlContent j, XmlContent k, XmlContent l, XmlContent m, XmlContent n, XmlContent o, XmlContent p) => XmlContent (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

parseContents :: XMLParser (OneOf16 a b c d e f g h i j k l m n o p) Source #

toContents :: OneOf16 a b c d e f g h i j k l m n o p -> [Content ()] Source #

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

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

foldOneOf16 :: (a -> z) -> (b -> z) -> (c -> z) -> (d -> z) -> (e -> z) -> (f -> z) -> (g -> z) -> (h -> z) -> (i -> z) -> (j -> z) -> (k -> z) -> (l -> z) -> (m -> z) -> (n -> z) -> (o -> z) -> (p -> z) -> OneOf16 a b c d e f g h i j k l m n o p -> z Source #

data OneOf17 a b c d e f g h i j k l m n o p q Source #

Instances
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o, Eq p, Eq q) => Eq (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

(==) :: OneOf17 a b c d e f g h i j k l m n o p q -> OneOf17 a b c d e f g h i j k l m n o p q -> Bool #

(/=) :: OneOf17 a b c d e f g h i j k l m n o p q -> OneOf17 a b c d e f g h i j k l m n o p q -> Bool #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n, Show o, Show p, Show q) => Show (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

showsPrec :: Int -> OneOf17 a b c d e f g h i j k l m n o p q -> ShowS #

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

showList :: [OneOf17 a b c d e f g h i j k l m n o p q] -> ShowS #

(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 #

(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i, XmlContent j, XmlContent k, XmlContent l, XmlContent m, XmlContent n, XmlContent o, XmlContent p, XmlContent q) => XmlContent (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

parseContents :: XMLParser (OneOf17 a b c d e f g h i j k l m n o p q) Source #

toContents :: OneOf17 a b c d e f g h i j k l m n o p q -> [Content ()] Source #

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

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

foldOneOf17 :: (a -> z) -> (b -> z) -> (c -> z) -> (d -> z) -> (e -> z) -> (f -> z) -> (g -> z) -> (h -> z) -> (i -> z) -> (j -> z) -> (k -> z) -> (l -> z) -> (m -> z) -> (n -> z) -> (o -> z) -> (p -> z) -> (q -> z) -> OneOf17 a b c d e f g h i j k l m n o p q -> z Source #

data OneOf18 a b c d e f g h i j k l m n o p q r Source #

Instances
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o, Eq p, Eq q, Eq r) => Eq (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

(==) :: OneOf18 a b c d e f g h i j k l m n o p q r -> OneOf18 a b c d e f g h i j k l m n o p q r -> Bool #

(/=) :: OneOf18 a b c d e f g h i j k l m n o p q r -> OneOf18 a b c d e f g h i j k l m n o p q r -> Bool #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n, Show o, Show p, Show q, Show r) => Show (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

showsPrec :: Int -> OneOf18 a b c d e f g h i j k l m n o p q r -> ShowS #

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

showList :: [OneOf18 a b c d e f g h i j k l m n o p q r] -> ShowS #

(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 #

(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i, XmlContent j, XmlContent k, XmlContent l, XmlContent m, XmlContent n, XmlContent o, XmlContent p, XmlContent q, XmlContent r) => XmlContent (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

parseContents :: XMLParser (OneOf18 a b c d e f g h i j k l m n o p q r) Source #

toContents :: OneOf18 a b c d e f g h i j k l m n o p q r -> [Content ()] Source #

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

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

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

data OneOf19 a b c d e f g h i j k l m n o p q r s Source #

Instances
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o, Eq p, Eq q, Eq r, Eq s) => Eq (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

(==) :: OneOf19 a b c d e f g h i j k l m n o p q r s -> OneOf19 a b c d e f g h i j k l m n o p q r s -> Bool #

(/=) :: OneOf19 a b c d e f g h i j k l m n o p q r s -> OneOf19 a b c d e f g h i j k l m n o p q r s -> Bool #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n, Show o, Show p, Show q, Show r, Show s) => Show (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

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

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

showList :: [OneOf19 a b c d e f g h i j k l m n o p q r s] -> ShowS #

(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 #

(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i, XmlContent j, XmlContent k, XmlContent l, XmlContent m, XmlContent n, XmlContent o, XmlContent p, XmlContent q, XmlContent r, XmlContent s) => XmlContent (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

parseContents :: XMLParser (OneOf19 a b c d e f g h i j k l m n o p q r s) Source #

toContents :: OneOf19 a b c d e f g h i j k l m n o p q r s -> [Content ()] Source #

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

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

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

data OneOf20 a b c d e f g h i j k l m n o p q r s t Source #

Instances
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o, Eq p, Eq q, Eq r, Eq s, Eq t) => Eq (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

(==) :: OneOf20 a b c d e f g h i j k l m n o p q r s t -> OneOf20 a b c d e f g h i j k l m n o p q r s t -> Bool #

(/=) :: OneOf20 a b c d e f g h i j k l m n o p q r s t -> OneOf20 a b c d e f g h i j k l m n o p q r s t -> Bool #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n, Show o, Show p, Show q, Show r, Show s, Show t) => Show (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

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

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

showList :: [OneOf20 a b c d e f g h i j k l m n o p q r s t] -> ShowS #

(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 #

(XmlContent a, XmlContent b, XmlContent c, XmlContent d, XmlContent e, XmlContent f, XmlContent g, XmlContent h, XmlContent i, XmlContent j, XmlContent k, XmlContent l, XmlContent m, XmlContent n, XmlContent o, XmlContent p, XmlContent q, XmlContent r, XmlContent s, XmlContent t) => XmlContent (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

parseContents :: XMLParser (OneOf20 a b c d e f g h i j k l m n o p q r s t) Source #

toContents :: OneOf20 a b c d e f g h i j k l m n o p q r s t -> [Content ()] Source #

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

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

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