Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Synopsis
- class SimpleType a where
- acceptingParser :: TextParser a
- simpleTypeText :: a -> String
- newtype XsdString = XsdString String
- type Boolean = Bool
- data Base64Binary = Base64Binary String
- data HexBinary = HexBinary String
- data Float
- data Decimal = Decimal Double
- data Double
- data AnyURI = AnyURI String
- data QName
- data NOTATION = NOTATION String
- data Duration = Duration Bool Int Int Int Int Int Float
- data DateTime = DateTime String
- data Time = Time String
- data Date = Date String
- data GYearMonth = GYearMonth String
- data GYear = GYear String
- data GMonthDay = GMonthDay String
- data GDay = GDay String
- data GMonth = GMonth String
- newtype NormalizedString = Normalized String
- newtype Token = Token String
- newtype Language = Language String
- newtype Name = Name String
- newtype NCName = NCName String
- newtype ID = ID String
- newtype IDREF = IDREF String
- newtype IDREFS = IDREFS String
- newtype ENTITY = ENTITY String
- newtype ENTITIES = ENTITIES String
- newtype NMTOKEN = NMTOKEN String
- newtype NMTOKENS = NMTOKENS String
- data Integer
- newtype NonPositiveInteger = NonPos Integer
- newtype NegativeInteger = Negative Integer
- newtype Long = Long Int64
- data Int
- newtype Short = Short Int16
- newtype Byte = Byte Int8
- newtype NonNegativeInteger = NonNeg Integer
- newtype UnsignedLong = ULong Word64
- newtype UnsignedInt = UInt Word32
- newtype UnsignedShort = UShort Word16
- newtype UnsignedByte = UByte Word8
- newtype PositiveInteger = Positive Integer
Type class for parsing simpleTypes
class SimpleType a where Source #
Ultimately, an XML parser will find some plain text as the content of a simpleType, which will need to be parsed. We use a TextParser, because values of simpleTypes can also be given elsewhere, e.g. as attribute values in an XSD definition, e.g. to restrict the permissible values of the simpleType. Such restrictions are therefore implemented as layered parsers.
acceptingParser :: TextParser a Source #
simpleTypeText :: a -> String Source #
Instances
Primitive XSD datatypes
XsdString String |
Instances
Eq XsdString Source # | |
Show XsdString Source # | |
SimpleType XsdString Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser XsdString Source # simpleTypeText :: XsdString -> String Source # | |
SchemaType XsdString Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser XsdString Source # schemaTypeToXML :: String -> XsdString -> [Content ()] Source # |
data Base64Binary Source #
Base64Binary String |
Instances
Eq Base64Binary Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: Base64Binary -> Base64Binary -> Bool (/=) :: Base64Binary -> Base64Binary -> Bool | |
Show Base64Binary Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> Base64Binary -> ShowS show :: Base64Binary -> String showList :: [Base64Binary] -> ShowS | |
SimpleType Base64Binary Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser Base64Binary Source # simpleTypeText :: Base64Binary -> String Source # | |
SchemaType Base64Binary Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser Base64Binary Source # schemaTypeToXML :: String -> Base64Binary -> [Content ()] Source # |
HexBinary String |
Instances
Eq HexBinary Source # | |
Show HexBinary Source # | |
SimpleType HexBinary Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser HexBinary Source # simpleTypeText :: HexBinary -> String Source # | |
SchemaType HexBinary Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser HexBinary Source # schemaTypeToXML :: String -> HexBinary -> [Content ()] Source # |
Instances
Eq Float | |
Floating Float | |
Ord Float | |
Read Float | |
RealFloat Float | |
Defined in GHC.Float floatRadix :: Float -> Integer floatDigits :: Float -> Int floatRange :: Float -> (Int, Int) decodeFloat :: Float -> (Integer, Int) encodeFloat :: Integer -> Int -> Float significand :: Float -> Float scaleFloat :: Int -> Float -> Float isInfinite :: Float -> Bool isDenormalized :: Float -> Bool isNegativeZero :: Float -> Bool | |
Parse Float | |
SimpleType Float Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser Float Source # simpleTypeText :: Float -> String Source # | |
HTypeable Float Source # | |
XmlContent Float Source # | |
SchemaType Float Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser Float Source # schemaTypeToXML :: String -> Float -> [Content ()] Source # | |
Generic1 (URec Float :: k -> Type) | |
Foldable (UFloat :: Type -> Type) | |
Defined in Data.Foldable fold :: Monoid m => UFloat m -> m foldMap :: Monoid m => (a -> m) -> UFloat a -> m foldMap' :: Monoid m => (a -> m) -> UFloat a -> m foldr :: (a -> b -> b) -> b -> UFloat a -> b foldr' :: (a -> b -> b) -> b -> UFloat a -> b foldl :: (b -> a -> b) -> b -> UFloat a -> b foldl' :: (b -> a -> b) -> b -> UFloat a -> b foldr1 :: (a -> a -> a) -> UFloat a -> a foldl1 :: (a -> a -> a) -> UFloat a -> a toList :: UFloat a -> [a] null :: UFloat a -> Bool elem :: Eq a => a -> UFloat a -> Bool maximum :: Ord a => UFloat a -> a minimum :: Ord a => UFloat a -> a sum :: Num a => UFloat a -> a product :: Num a => UFloat a -> a | |
Traversable (UFloat :: Type -> Type) | |
Defined in Data.Traversable | |
Functor (URec Float :: Type -> Type) | |
Eq (URec Float p) | |
Ord (URec Float p) | |
Defined in GHC.Generics | |
Show (URec Float p) | |
Generic (URec Float p) | |
data URec Float (p :: k) | |
Defined in GHC.Generics | |
type Rep1 (URec Float :: k -> Type) | |
Defined in GHC.Generics type Rep1 (URec Float :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UFloat" 'PrefixI 'True) (S1 ('MetaSel ('Just "uFloat#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UFloat :: k -> Type))) | |
type Rep (URec Float p) | |
Defined in GHC.Generics type Rep (URec Float p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UFloat" 'PrefixI 'True) (S1 ('MetaSel ('Just "uFloat#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UFloat :: Type -> Type))) |
Instances
Eq Decimal Source # | |
Show Decimal Source # | |
SimpleType Decimal Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser Decimal Source # simpleTypeText :: Decimal -> String Source # | |
SchemaType Decimal Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser Decimal Source # schemaTypeToXML :: String -> Decimal -> [Content ()] Source # |
Instances
Eq Double | |
Floating Double | |
Ord Double | |
Read Double | |
RealFloat Double | |
Defined in GHC.Float floatRadix :: Double -> Integer floatDigits :: Double -> Int floatRange :: Double -> (Int, Int) decodeFloat :: Double -> (Integer, Int) encodeFloat :: Integer -> Int -> Double significand :: Double -> Double scaleFloat :: Int -> Double -> Double isInfinite :: Double -> Bool isDenormalized :: Double -> Bool isNegativeZero :: Double -> Bool | |
Parse Double | |
SimpleType Double Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser Double Source # simpleTypeText :: Double -> String Source # | |
HTypeable Double Source # | |
XmlContent Double Source # | |
SchemaType Double Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser Double Source # schemaTypeToXML :: String -> Double -> [Content ()] Source # | |
Generic1 (URec Double :: k -> Type) | |
Foldable (UDouble :: Type -> Type) | |
Defined in Data.Foldable fold :: Monoid m => UDouble m -> m foldMap :: Monoid m => (a -> m) -> UDouble a -> m foldMap' :: Monoid m => (a -> m) -> UDouble a -> m foldr :: (a -> b -> b) -> b -> UDouble a -> b foldr' :: (a -> b -> b) -> b -> UDouble a -> b foldl :: (b -> a -> b) -> b -> UDouble a -> b foldl' :: (b -> a -> b) -> b -> UDouble a -> b foldr1 :: (a -> a -> a) -> UDouble a -> a foldl1 :: (a -> a -> a) -> UDouble a -> a toList :: UDouble a -> [a] null :: UDouble a -> Bool elem :: Eq a => a -> UDouble a -> Bool maximum :: Ord a => UDouble a -> a minimum :: Ord a => UDouble a -> a sum :: Num a => UDouble a -> a product :: Num a => UDouble a -> a | |
Traversable (UDouble :: Type -> Type) | |
Defined in Data.Traversable | |
Functor (URec Double :: Type -> Type) | |
Eq (URec Double p) | |
Ord (URec Double p) | |
Defined in GHC.Generics | |
Show (URec Double p) | |
Generic (URec Double p) | |
data URec Double (p :: k) | |
Defined in GHC.Generics | |
type Rep1 (URec Double :: k -> Type) | |
Defined in GHC.Generics type Rep1 (URec Double :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UDouble" 'PrefixI 'True) (S1 ('MetaSel ('Just "uDouble#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UDouble :: k -> Type))) | |
type Rep (URec Double p) | |
Defined in GHC.Generics type Rep (URec Double p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UDouble" 'PrefixI 'True) (S1 ('MetaSel ('Just "uDouble#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UDouble :: Type -> Type))) |
AnyURI String |
Instances
Eq AnyURI Source # | |
Show AnyURI Source # | |
SimpleType AnyURI Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser AnyURI Source # simpleTypeText :: AnyURI -> String Source # | |
SchemaType AnyURI Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser AnyURI Source # schemaTypeToXML :: String -> AnyURI -> [Content ()] Source # |
A QName is a (possibly) qualified name, in the sense of XML namespaces.
NOTATION String |
Instances
Eq NOTATION Source # | |
Show NOTATION Source # | |
SimpleType NOTATION Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser NOTATION Source # simpleTypeText :: NOTATION -> String Source # | |
SchemaType NOTATION Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser NOTATION Source # schemaTypeToXML :: String -> NOTATION -> [Content ()] Source # |
Instances
Eq Duration Source # | |
Show Duration Source # | |
SimpleType Duration Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser Duration Source # simpleTypeText :: Duration -> String Source # | |
SchemaType Duration Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser Duration Source # schemaTypeToXML :: String -> Duration -> [Content ()] Source # |
DateTime String |
Instances
Eq DateTime Source # | |
Show DateTime Source # | |
SimpleType DateTime Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser DateTime Source # simpleTypeText :: DateTime -> String Source # | |
SchemaType DateTime Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser DateTime Source # schemaTypeToXML :: String -> DateTime -> [Content ()] Source # |
Time String |
Instances
Eq Time Source # | |
Show Time Source # | |
SimpleType Time Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser Time Source # simpleTypeText :: Time -> String Source # | |
SchemaType Time Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser Time Source # schemaTypeToXML :: String -> Time -> [Content ()] Source # |
Date String |
Instances
Eq Date Source # | |
Show Date Source # | |
SimpleType Date Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser Date Source # simpleTypeText :: Date -> String Source # | |
SchemaType Date Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser Date Source # schemaTypeToXML :: String -> Date -> [Content ()] Source # |
data GYearMonth Source #
GYearMonth String |
Instances
Eq GYearMonth Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: GYearMonth -> GYearMonth -> Bool (/=) :: GYearMonth -> GYearMonth -> Bool | |
Show GYearMonth Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> GYearMonth -> ShowS show :: GYearMonth -> String showList :: [GYearMonth] -> ShowS | |
SimpleType GYearMonth Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser GYearMonth Source # simpleTypeText :: GYearMonth -> String Source # | |
SchemaType GYearMonth Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser GYearMonth Source # schemaTypeToXML :: String -> GYearMonth -> [Content ()] Source # |
GYear String |
Instances
Eq GYear Source # | |
Show GYear Source # | |
SimpleType GYear Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser GYear Source # simpleTypeText :: GYear -> String Source # | |
SchemaType GYear Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser GYear Source # schemaTypeToXML :: String -> GYear -> [Content ()] Source # |
GMonthDay String |
Instances
Eq GMonthDay Source # | |
Show GMonthDay Source # | |
SimpleType GMonthDay Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser GMonthDay Source # simpleTypeText :: GMonthDay -> String Source # | |
SchemaType GMonthDay Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser GMonthDay Source # schemaTypeToXML :: String -> GMonthDay -> [Content ()] Source # |
GDay String |
Instances
Eq GDay Source # | |
Show GDay Source # | |
SimpleType GDay Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser GDay Source # simpleTypeText :: GDay -> String Source # | |
SchemaType GDay Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser GDay Source # schemaTypeToXML :: String -> GDay -> [Content ()] Source # |
GMonth String |
Instances
Eq GMonth Source # | |
Show GMonth Source # | |
SimpleType GMonth Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser GMonth Source # simpleTypeText :: GMonth -> String Source # | |
SchemaType GMonth Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser GMonth Source # schemaTypeToXML :: String -> GMonth -> [Content ()] Source # |
Derived, yet builtin, datatypes
newtype NormalizedString Source #
Normalized String |
Instances
Eq NormalizedString Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: NormalizedString -> NormalizedString -> Bool (/=) :: NormalizedString -> NormalizedString -> Bool | |
Show NormalizedString Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> NormalizedString -> ShowS show :: NormalizedString -> String showList :: [NormalizedString] -> ShowS | |
SimpleType NormalizedString Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser NormalizedString Source # simpleTypeText :: NormalizedString -> String Source # | |
SchemaType NormalizedString Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser NormalizedString Source # schemaTypeToXML :: String -> NormalizedString -> [Content ()] Source # |
Token String |
Instances
Eq Token Source # | |
Show Token Source # | |
SimpleType Token Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser Token Source # simpleTypeText :: Token -> String Source # | |
SchemaType Token Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser Token Source # schemaTypeToXML :: String -> Token -> [Content ()] Source # |
Language String |
Instances
Eq Language Source # | |
Show Language Source # | |
SimpleType Language Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser Language Source # simpleTypeText :: Language -> String Source # | |
SchemaType Language Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser Language Source # schemaTypeToXML :: String -> Language -> [Content ()] Source # |
Name String |
Instances
Eq Name Source # | |
Show Name Source # | |
SimpleType Name Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser Name Source # simpleTypeText :: Name -> String Source # | |
SchemaType Name Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser Name Source # schemaTypeToXML :: String -> Name -> [Content ()] Source # |
NCName String |
Instances
Eq NCName Source # | |
Show NCName Source # | |
SimpleType NCName Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser NCName Source # simpleTypeText :: NCName -> String Source # | |
SchemaType NCName Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser NCName Source # schemaTypeToXML :: String -> NCName -> [Content ()] Source # |
ID String |
Instances
Eq ID Source # | |
Show ID Source # | |
SimpleType ID Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser ID Source # simpleTypeText :: ID -> String Source # | |
SchemaType ID Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser ID Source # schemaTypeToXML :: String -> ID -> [Content ()] Source # |
IDREF String |
Instances
Eq IDREF Source # | |
Show IDREF Source # | |
SimpleType IDREF Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser IDREF Source # simpleTypeText :: IDREF -> String Source # | |
SchemaType IDREF Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser IDREF Source # schemaTypeToXML :: String -> IDREF -> [Content ()] Source # |
IDREFS String |
Instances
Eq IDREFS Source # | |
Show IDREFS Source # | |
SimpleType IDREFS Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser IDREFS Source # simpleTypeText :: IDREFS -> String Source # | |
SchemaType IDREFS Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser IDREFS Source # schemaTypeToXML :: String -> IDREFS -> [Content ()] Source # |
ENTITY String |
Instances
Eq ENTITY Source # | |
Show ENTITY Source # | |
SimpleType ENTITY Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser ENTITY Source # simpleTypeText :: ENTITY -> String Source # | |
SchemaType ENTITY Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser ENTITY Source # schemaTypeToXML :: String -> ENTITY -> [Content ()] Source # |
ENTITIES String |
Instances
Eq ENTITIES Source # | |
Show ENTITIES Source # | |
SimpleType ENTITIES Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser ENTITIES Source # simpleTypeText :: ENTITIES -> String Source # | |
SchemaType ENTITIES Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser ENTITIES Source # schemaTypeToXML :: String -> ENTITIES -> [Content ()] Source # |
NMTOKEN String |
Instances
Eq NMTOKEN Source # | |
Show NMTOKEN Source # | |
SimpleType NMTOKEN Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser NMTOKEN Source # simpleTypeText :: NMTOKEN -> String Source # | |
SchemaType NMTOKEN Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser NMTOKEN Source # schemaTypeToXML :: String -> NMTOKEN -> [Content ()] Source # |
NMTOKENS String |
Instances
Eq NMTOKENS Source # | |
Show NMTOKENS Source # | |
SimpleType NMTOKENS Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser NMTOKENS Source # simpleTypeText :: NMTOKENS -> String Source # | |
SchemaType NMTOKENS Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser NMTOKENS Source # schemaTypeToXML :: String -> NMTOKENS -> [Content ()] Source # |
Instances
Enum Integer | |
Defined in GHC.Enum | |
Eq Integer | |
Integral Integer | |
Num Integer | |
Ord Integer | |
Read Integer | |
Real Integer | |
Defined in GHC.Real toRational :: Integer -> Rational | |
Show Integer | |
Ix Integer | |
Parse Integer | |
SimpleType Integer Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser Integer Source # simpleTypeText :: Integer -> String Source # | |
HTypeable Integer Source # | |
XmlContent Integer Source # | |
SchemaType Integer Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser Integer Source # schemaTypeToXML :: String -> Integer -> [Content ()] Source # |
newtype NonPositiveInteger Source #
Instances
Eq NonPositiveInteger Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: NonPositiveInteger -> NonPositiveInteger -> Bool (/=) :: NonPositiveInteger -> NonPositiveInteger -> Bool | |
Show NonPositiveInteger Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> NonPositiveInteger -> ShowS show :: NonPositiveInteger -> String showList :: [NonPositiveInteger] -> ShowS | |
SimpleType NonPositiveInteger Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser NonPositiveInteger Source # simpleTypeText :: NonPositiveInteger -> String Source # | |
SchemaType NonPositiveInteger Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser NonPositiveInteger Source # schemaTypeToXML :: String -> NonPositiveInteger -> [Content ()] Source # |
newtype NegativeInteger Source #
Instances
Eq NegativeInteger Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: NegativeInteger -> NegativeInteger -> Bool (/=) :: NegativeInteger -> NegativeInteger -> Bool | |
Show NegativeInteger Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> NegativeInteger -> ShowS show :: NegativeInteger -> String showList :: [NegativeInteger] -> ShowS | |
SimpleType NegativeInteger Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser NegativeInteger Source # simpleTypeText :: NegativeInteger -> String Source # | |
SchemaType NegativeInteger Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser NegativeInteger Source # schemaTypeToXML :: String -> NegativeInteger -> [Content ()] Source # |
Long Int64 |
Instances
Eq Long Source # | |
Show Long Source # | |
SimpleType Long Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser Long Source # simpleTypeText :: Long -> String Source # | |
SchemaType Long Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser Long Source # schemaTypeToXML :: String -> Long -> [Content ()] Source # |
Instances
Bounded Int | |
Enum Int | |
Eq Int | |
Integral Int | |
Num Int | |
Ord Int | |
Read Int | |
Real Int | |
Defined in GHC.Real toRational :: Int -> Rational | |
Show Int | |
Ix Int | |
Parse Int | |
SimpleType Int Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser Int Source # simpleTypeText :: Int -> String Source # | |
HTypeable Int Source # | |
XmlContent Int Source # | |
SchemaType Int Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser Int Source # schemaTypeToXML :: String -> Int -> [Content ()] Source # | |
Generic1 (URec Int :: k -> Type) | |
Foldable (UInt :: Type -> Type) | |
Defined in Data.Foldable fold :: Monoid m => UInt m -> m foldMap :: Monoid m => (a -> m) -> UInt a -> m foldMap' :: Monoid m => (a -> m) -> UInt a -> m foldr :: (a -> b -> b) -> b -> UInt a -> b foldr' :: (a -> b -> b) -> b -> UInt a -> b foldl :: (b -> a -> b) -> b -> UInt a -> b foldl' :: (b -> a -> b) -> b -> UInt a -> b foldr1 :: (a -> a -> a) -> UInt a -> a foldl1 :: (a -> a -> a) -> UInt a -> a toList :: UInt a -> [a] null :: UInt a -> Bool elem :: Eq a => a -> UInt a -> Bool maximum :: Ord a => UInt a -> a minimum :: Ord a => UInt a -> a sum :: Num a => UInt a -> a product :: Num a => UInt a -> a | |
Traversable (UInt :: Type -> Type) | |
Defined in Data.Traversable | |
Functor (URec Int :: Type -> Type) | |
Eq (URec Int p) | |
Ord (URec Int p) | |
Defined in GHC.Generics | |
Show (URec Int p) | |
Generic (URec Int p) | |
data URec Int (p :: k) | |
Defined in GHC.Generics | |
type Rep1 (URec Int :: k -> Type) | |
Defined in GHC.Generics type Rep1 (URec Int :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UInt" 'PrefixI 'True) (S1 ('MetaSel ('Just "uInt#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UInt :: k -> Type))) | |
type Rep (URec Int p) | |
Defined in GHC.Generics type Rep (URec Int p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UInt" 'PrefixI 'True) (S1 ('MetaSel ('Just "uInt#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UInt :: Type -> Type))) |
Short Int16 |
Instances
Eq Short Source # | |
Show Short Source # | |
SimpleType Short Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser Short Source # simpleTypeText :: Short -> String Source # | |
SchemaType Short Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser Short Source # schemaTypeToXML :: String -> Short -> [Content ()] Source # |
Byte Int8 |
Instances
Eq Byte Source # | |
Show Byte Source # | |
SimpleType Byte Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser Byte Source # simpleTypeText :: Byte -> String Source # | |
SchemaType Byte Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser Byte Source # schemaTypeToXML :: String -> Byte -> [Content ()] Source # |
newtype NonNegativeInteger Source #
Instances
Eq NonNegativeInteger Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: NonNegativeInteger -> NonNegativeInteger -> Bool (/=) :: NonNegativeInteger -> NonNegativeInteger -> Bool | |
Show NonNegativeInteger Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> NonNegativeInteger -> ShowS show :: NonNegativeInteger -> String showList :: [NonNegativeInteger] -> ShowS | |
SimpleType NonNegativeInteger Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser NonNegativeInteger Source # simpleTypeText :: NonNegativeInteger -> String Source # | |
SchemaType NonNegativeInteger Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser NonNegativeInteger Source # schemaTypeToXML :: String -> NonNegativeInteger -> [Content ()] Source # |
newtype UnsignedLong Source #
ULong Word64 |
Instances
Eq UnsignedLong Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: UnsignedLong -> UnsignedLong -> Bool (/=) :: UnsignedLong -> UnsignedLong -> Bool | |
Show UnsignedLong Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> UnsignedLong -> ShowS show :: UnsignedLong -> String showList :: [UnsignedLong] -> ShowS | |
SimpleType UnsignedLong Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser UnsignedLong Source # simpleTypeText :: UnsignedLong -> String Source # | |
SchemaType UnsignedLong Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser UnsignedLong Source # schemaTypeToXML :: String -> UnsignedLong -> [Content ()] Source # |
newtype UnsignedInt Source #
UInt Word32 |
Instances
Eq UnsignedInt Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: UnsignedInt -> UnsignedInt -> Bool (/=) :: UnsignedInt -> UnsignedInt -> Bool | |
Show UnsignedInt Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> UnsignedInt -> ShowS show :: UnsignedInt -> String showList :: [UnsignedInt] -> ShowS | |
SimpleType UnsignedInt Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser UnsignedInt Source # simpleTypeText :: UnsignedInt -> String Source # | |
SchemaType UnsignedInt Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser UnsignedInt Source # schemaTypeToXML :: String -> UnsignedInt -> [Content ()] Source # |
newtype UnsignedShort Source #
UShort Word16 |
Instances
Eq UnsignedShort Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: UnsignedShort -> UnsignedShort -> Bool (/=) :: UnsignedShort -> UnsignedShort -> Bool | |
Show UnsignedShort Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> UnsignedShort -> ShowS show :: UnsignedShort -> String showList :: [UnsignedShort] -> ShowS | |
SimpleType UnsignedShort Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser UnsignedShort Source # simpleTypeText :: UnsignedShort -> String Source # | |
SchemaType UnsignedShort Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser UnsignedShort Source # schemaTypeToXML :: String -> UnsignedShort -> [Content ()] Source # |
newtype UnsignedByte Source #
UByte Word8 |
Instances
Eq UnsignedByte Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: UnsignedByte -> UnsignedByte -> Bool (/=) :: UnsignedByte -> UnsignedByte -> Bool | |
Show UnsignedByte Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> UnsignedByte -> ShowS show :: UnsignedByte -> String showList :: [UnsignedByte] -> ShowS | |
SimpleType UnsignedByte Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser UnsignedByte Source # simpleTypeText :: UnsignedByte -> String Source # | |
SchemaType UnsignedByte Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser UnsignedByte Source # schemaTypeToXML :: String -> UnsignedByte -> [Content ()] Source # |
newtype PositiveInteger Source #
Instances
Eq PositiveInteger Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: PositiveInteger -> PositiveInteger -> Bool (/=) :: PositiveInteger -> PositiveInteger -> Bool | |
Show PositiveInteger Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> PositiveInteger -> ShowS show :: PositiveInteger -> String showList :: [PositiveInteger] -> ShowS | |
SimpleType PositiveInteger Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser PositiveInteger Source # simpleTypeText :: PositiveInteger -> String Source # | |
SchemaType PositiveInteger Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser PositiveInteger Source # schemaTypeToXML :: String -> PositiveInteger -> [Content ()] Source # |