Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Synopsis
- class SimpleType a where
- acceptingParser :: TextParser a
- simpleTypeText :: a -> String
- module Text.Parse
- 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
module Text.Parse
Primitive XSD datatypes
Instances
SimpleType XsdString Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType XsdString Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
Show XsdString Source # | |
Eq XsdString Source # | |
data Base64Binary Source #
Instances
SimpleType Base64Binary Source # | |
SchemaType Base64Binary Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser Base64Binary Source # schemaTypeToXML :: String -> Base64Binary -> [Content ()] Source # | |
Show Base64Binary Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> Base64Binary -> ShowS # show :: Base64Binary -> String # showList :: [Base64Binary] -> ShowS # | |
Eq Base64Binary Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: Base64Binary -> Base64Binary -> Bool # (/=) :: Base64Binary -> Base64Binary -> Bool # |
Instances
SimpleType HexBinary Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType HexBinary Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
Show HexBinary Source # | |
Eq HexBinary Source # | |
Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.
Instances
SimpleType Float Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType Float Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
HTypeable Float Source # | |
XmlContent Float Source # | |
Floating Float | Since: base-2.1 |
RealFloat Float | Since: base-2.1 |
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 # | |
Read Float | Since: base-2.1 |
Eq Float | Note that due to the presence of
Also note that
|
Ord Float | Note that due to the presence of
Also note that, due to the same,
|
Parse Float | |
Defined in Text.Parse | |
Lift Float | |
Generic1 (URec Float :: k -> Type) | |
Foldable (UFloat :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
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 # elem :: Eq a => a -> UFloat a -> Bool # maximum :: Ord a => UFloat a -> a # minimum :: Ord a => UFloat a -> a # | |
Traversable (UFloat :: Type -> Type) | Since: base-4.9.0.0 |
Functor (URec Float :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
Generic (URec Float p) | |
Show (URec Float p) | |
Eq (URec Float p) | |
Ord (URec Float p) | |
Defined in GHC.Generics | |
data URec Float (p :: k) | Used for marking occurrences of Since: base-4.9.0.0 |
type Rep1 (URec Float :: k -> Type) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Float p) | |
Defined in GHC.Generics |
Instances
SimpleType Decimal Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType Decimal Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
Show Decimal Source # | |
Eq Decimal Source # | |
Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.
Instances
SimpleType Double Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType Double Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
HTypeable Double Source # | |
XmlContent Double Source # | |
Floating Double | Since: base-2.1 |
RealFloat Double | Since: base-2.1 |
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 # | |
Read Double | Since: base-2.1 |
Eq Double | Note that due to the presence of
Also note that
|
Ord Double | Note that due to the presence of
Also note that, due to the same,
|
Parse Double | |
Defined in Text.Parse parse :: TextParser Double # parsePrec :: Int -> TextParser Double # parseList :: TextParser [Double] # | |
Lift Double | |
Generic1 (URec Double :: k -> Type) | |
Foldable (UDouble :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
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 # elem :: Eq a => a -> UDouble a -> Bool # maximum :: Ord a => UDouble a -> a # minimum :: Ord a => UDouble a -> a # | |
Traversable (UDouble :: Type -> Type) | Since: base-4.9.0.0 |
Functor (URec Double :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
Generic (URec Double p) | |
Show (URec Double p) | Since: base-4.9.0.0 |
Eq (URec Double p) | Since: base-4.9.0.0 |
Ord (URec Double p) | Since: base-4.9.0.0 |
Defined in GHC.Generics compare :: URec Double p -> URec Double p -> Ordering # (<) :: URec Double p -> URec Double p -> Bool # (<=) :: URec Double p -> URec Double p -> Bool # (>) :: URec Double p -> URec Double p -> Bool # (>=) :: URec Double p -> URec Double p -> Bool # | |
data URec Double (p :: k) | Used for marking occurrences of Since: base-4.9.0.0 |
type Rep1 (URec Double :: k -> Type) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Double p) | Since: base-4.9.0.0 |
Defined in GHC.Generics |
Instances
SimpleType AnyURI Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType AnyURI Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
Show AnyURI Source # | |
Eq AnyURI Source # | |
A QName is a (possibly) qualified name, in the sense of XML namespaces.
Instances
SimpleType NOTATION Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType NOTATION Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
Show NOTATION Source # | |
Eq NOTATION Source # | |
Instances
SimpleType Duration Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType Duration Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
Show Duration Source # | |
Eq Duration Source # | |
Instances
SimpleType DateTime Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType DateTime Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
Show DateTime Source # | |
Eq DateTime Source # | |
Instances
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 | |
Show Time Source # | |
Eq Time Source # | |
Instances
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 | |
Show Date Source # | |
Eq Date Source # | |
data GYearMonth Source #
Instances
SimpleType GYearMonth Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType GYearMonth Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser GYearMonth Source # schemaTypeToXML :: String -> GYearMonth -> [Content ()] Source # | |
Show GYearMonth Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> GYearMonth -> ShowS # show :: GYearMonth -> String # showList :: [GYearMonth] -> ShowS # | |
Eq GYearMonth Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: GYearMonth -> GYearMonth -> Bool # (/=) :: GYearMonth -> GYearMonth -> Bool # |
Instances
SimpleType GYear Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType GYear Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
Show GYear Source # | |
Eq GYear Source # | |
Instances
SimpleType GMonthDay Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType GMonthDay Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
Show GMonthDay Source # | |
Eq GMonthDay Source # | |
Instances
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 | |
Show GDay Source # | |
Eq GDay Source # | |
Instances
SimpleType GMonth Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType GMonth Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
Show GMonth Source # | |
Eq GMonth Source # | |
Derived, yet builtin, datatypes
newtype NormalizedString Source #
Instances
SimpleType NormalizedString Source # | |
SchemaType NormalizedString Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser NormalizedString Source # schemaTypeToXML :: String -> NormalizedString -> [Content ()] Source # | |
Show NormalizedString Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> NormalizedString -> ShowS # show :: NormalizedString -> String # showList :: [NormalizedString] -> ShowS # | |
Eq NormalizedString Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: NormalizedString -> NormalizedString -> Bool # (/=) :: NormalizedString -> NormalizedString -> Bool # |
Instances
SimpleType Token Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType Token Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
Show Token Source # | |
Eq Token Source # | |
Instances
SimpleType Language Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType Language Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
Show Language Source # | |
Eq Language Source # | |
Instances
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 | |
Show Name Source # | |
Eq Name Source # | |
Instances
SimpleType NCName Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType NCName Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
Show NCName Source # | |
Eq NCName Source # | |
Instances
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 | |
Show ID Source # | |
Eq ID Source # | |
Instances
SimpleType IDREF Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType IDREF Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
Show IDREF Source # | |
Eq IDREF Source # | |
Instances
SimpleType IDREFS Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType IDREFS Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
Show IDREFS Source # | |
Eq IDREFS Source # | |
Instances
SimpleType ENTITY Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType ENTITY Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
Show ENTITY Source # | |
Eq ENTITY Source # | |
Instances
SimpleType ENTITIES Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType ENTITIES Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
Show ENTITIES Source # | |
Eq ENTITIES Source # | |
Instances
SimpleType NMTOKEN Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType NMTOKEN Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
Show NMTOKEN Source # | |
Eq NMTOKEN Source # | |
Instances
SimpleType NMTOKENS Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType NMTOKENS Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
Show NMTOKENS Source # | |
Eq NMTOKENS Source # | |
Arbitrary precision integers. In contrast with fixed-size integral types
such as Int
, the Integer
type represents the entire infinite range of
integers.
Integers are stored in a kind of sign-magnitude form, hence do not expect two's complement form when using bit operations.
If the value is small (fit into an Int
), IS
constructor is used.
Otherwise Integer
and IN
constructors are used to store a BigNat
representing respectively the positive or the negative value magnitude.
Invariant: Integer
and IN
are used iff value doesn't fit in IS
Instances
SimpleType Integer Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType Integer Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
HTypeable Integer Source # | |
XmlContent Integer Source # | |
Enum Integer | Since: base-2.1 |
Ix Integer | Since: base-2.1 |
Num Integer | Since: base-2.1 |
Read Integer | Since: base-2.1 |
Integral Integer | Since: base-2.0.1 |
Defined in GHC.Real | |
Real Integer | Since: base-2.0.1 |
Defined in GHC.Real toRational :: Integer -> Rational # | |
Show Integer | Since: base-2.1 |
Eq Integer | |
Ord Integer | |
Parse Integer | |
Defined in Text.Parse parse :: TextParser Integer # parsePrec :: Int -> TextParser Integer # parseList :: TextParser [Integer] # | |
Lift Integer | |
newtype NonPositiveInteger Source #
Instances
SimpleType NonPositiveInteger Source # | |
SchemaType NonPositiveInteger Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser NonPositiveInteger Source # schemaTypeToXML :: String -> NonPositiveInteger -> [Content ()] Source # | |
Show NonPositiveInteger Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> NonPositiveInteger -> ShowS # show :: NonPositiveInteger -> String # showList :: [NonPositiveInteger] -> ShowS # | |
Eq NonPositiveInteger Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: NonPositiveInteger -> NonPositiveInteger -> Bool # (/=) :: NonPositiveInteger -> NonPositiveInteger -> Bool # |
newtype NegativeInteger Source #
Instances
SimpleType NegativeInteger Source # | |
SchemaType NegativeInteger Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser NegativeInteger Source # schemaTypeToXML :: String -> NegativeInteger -> [Content ()] Source # | |
Show NegativeInteger Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> NegativeInteger -> ShowS # show :: NegativeInteger -> String # showList :: [NegativeInteger] -> ShowS # | |
Eq NegativeInteger Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: NegativeInteger -> NegativeInteger -> Bool # (/=) :: NegativeInteger -> NegativeInteger -> Bool # |
Instances
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 | |
Show Long Source # | |
Eq Long Source # | |
A fixed-precision integer type with at least the range [-2^29 .. 2^29-1]
.
The exact range for a given implementation can be determined by using
minBound
and maxBound
from the Bounded
class.
Instances
SimpleType Int Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes acceptingParser :: TextParser Int Source # simpleTypeText :: Int -> String Source # | |
SchemaType Int Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
HTypeable Int Source # | |
XmlContent Int Source # | |
Bounded Int | Since: base-2.1 |
Enum Int | Since: base-2.1 |
Ix Int | Since: base-2.1 |
Num Int | Since: base-2.1 |
Read Int | Since: base-2.1 |
Integral Int | Since: base-2.0.1 |
Real Int | Since: base-2.0.1 |
Defined in GHC.Real toRational :: Int -> Rational # | |
Show Int | Since: base-2.1 |
Eq Int | |
Ord Int | |
Parse Int | |
Defined in Text.Parse | |
Lift Int | |
Generic1 (URec Int :: k -> Type) | |
Foldable (UInt :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
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 # elem :: Eq a => a -> UInt a -> Bool # maximum :: Ord a => UInt a -> a # | |
Traversable (UInt :: Type -> Type) | Since: base-4.9.0.0 |
Functor (URec Int :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
Generic (URec Int p) | |
Show (URec Int p) | Since: base-4.9.0.0 |
Eq (URec Int p) | Since: base-4.9.0.0 |
Ord (URec Int p) | Since: base-4.9.0.0 |
data URec Int (p :: k) | Used for marking occurrences of Since: base-4.9.0.0 |
type Rep1 (URec Int :: k -> Type) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Int p) | Since: base-4.9.0.0 |
Defined in GHC.Generics |
Instances
SimpleType Short Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType Short Source # | |
Defined in Text.XML.HaXml.Schema.Schema | |
Show Short Source # | |
Eq Short Source # | |
Instances
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 | |
Show Byte Source # | |
Eq Byte Source # | |
newtype NonNegativeInteger Source #
Instances
SimpleType NonNegativeInteger Source # | |
SchemaType NonNegativeInteger Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser NonNegativeInteger Source # schemaTypeToXML :: String -> NonNegativeInteger -> [Content ()] Source # | |
Show NonNegativeInteger Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> NonNegativeInteger -> ShowS # show :: NonNegativeInteger -> String # showList :: [NonNegativeInteger] -> ShowS # | |
Eq NonNegativeInteger Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: NonNegativeInteger -> NonNegativeInteger -> Bool # (/=) :: NonNegativeInteger -> NonNegativeInteger -> Bool # |
newtype UnsignedLong Source #
Instances
SimpleType UnsignedLong Source # | |
SchemaType UnsignedLong Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser UnsignedLong Source # schemaTypeToXML :: String -> UnsignedLong -> [Content ()] Source # | |
Show UnsignedLong Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> UnsignedLong -> ShowS # show :: UnsignedLong -> String # showList :: [UnsignedLong] -> ShowS # | |
Eq UnsignedLong Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: UnsignedLong -> UnsignedLong -> Bool # (/=) :: UnsignedLong -> UnsignedLong -> Bool # |
newtype UnsignedInt Source #
Instances
SimpleType UnsignedInt Source # | |
SchemaType UnsignedInt Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser UnsignedInt Source # schemaTypeToXML :: String -> UnsignedInt -> [Content ()] Source # | |
Show UnsignedInt Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> UnsignedInt -> ShowS # show :: UnsignedInt -> String # showList :: [UnsignedInt] -> ShowS # | |
Eq UnsignedInt Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: UnsignedInt -> UnsignedInt -> Bool # (/=) :: UnsignedInt -> UnsignedInt -> Bool # |
newtype UnsignedShort Source #
Instances
SimpleType UnsignedShort Source # | |
SchemaType UnsignedShort Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser UnsignedShort Source # schemaTypeToXML :: String -> UnsignedShort -> [Content ()] Source # | |
Show UnsignedShort Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> UnsignedShort -> ShowS # show :: UnsignedShort -> String # showList :: [UnsignedShort] -> ShowS # | |
Eq UnsignedShort Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: UnsignedShort -> UnsignedShort -> Bool # (/=) :: UnsignedShort -> UnsignedShort -> Bool # |
newtype UnsignedByte Source #
Instances
SimpleType UnsignedByte Source # | |
SchemaType UnsignedByte Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser UnsignedByte Source # schemaTypeToXML :: String -> UnsignedByte -> [Content ()] Source # | |
Show UnsignedByte Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> UnsignedByte -> ShowS # show :: UnsignedByte -> String # showList :: [UnsignedByte] -> ShowS # | |
Eq UnsignedByte Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: UnsignedByte -> UnsignedByte -> Bool # (/=) :: UnsignedByte -> UnsignedByte -> Bool # |
newtype PositiveInteger Source #
Instances
SimpleType PositiveInteger Source # | |
SchemaType PositiveInteger Source # | |
Defined in Text.XML.HaXml.Schema.Schema parseSchemaType :: String -> XMLParser PositiveInteger Source # schemaTypeToXML :: String -> PositiveInteger -> [Content ()] Source # | |
Show PositiveInteger Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes showsPrec :: Int -> PositiveInteger -> ShowS # show :: PositiveInteger -> String # showList :: [PositiveInteger] -> ShowS # | |
Eq PositiveInteger Source # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes (==) :: PositiveInteger -> PositiveInteger -> Bool # (/=) :: PositiveInteger -> PositiveInteger -> Bool # |