Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Text.XML.HaXml.Schema.PrimitiveTypes
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 #
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.
Instances
module Text.Parse
Primitive XSD datatypes
Instances
Eq XsdString # | |
Show XsdString # | |
SimpleType XsdString # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType XsdString # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser XsdString # schemaTypeToXML :: String -> XsdString -> [Content ()] # |
data Base64Binary #
Constructors
Base64Binary String |
Instances
Eq Base64Binary # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
Show Base64Binary # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes Methods showsPrec :: Int -> Base64Binary -> ShowS # show :: Base64Binary -> String # showList :: [Base64Binary] -> ShowS # | |
SimpleType Base64Binary # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType Base64Binary # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser Base64Binary # schemaTypeToXML :: String -> Base64Binary -> [Content ()] # |
Instances
Eq HexBinary # | |
Show HexBinary # | |
SimpleType HexBinary # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType HexBinary # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser HexBinary # schemaTypeToXML :: String -> HexBinary -> [Content ()] # |
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
Eq Float | Note that due to the presence of
Also note that
|
Floating Float | Since: base-2.1 |
Ord Float | Note that due to the presence of
Also note that, due to the same,
|
Read Float | Since: base-2.1 |
RealFloat Float | Since: base-2.1 |
Defined in GHC.Float Methods 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 | |
Defined in Text.Parse Methods parse :: TextParser Float # parsePrec :: Int -> TextParser Float # parseList :: TextParser [Float] # | |
SimpleType Float # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
HTypeable Float # | |
Defined in Text.XML.HaXml.TypeMapping | |
XmlContent Float # | |
SchemaType Float # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser Float # schemaTypeToXML :: String -> Float -> [Content ()] # | |
Generic1 (URec Float :: k -> Type) | |
Functor (URec Float :: Type -> Type) | Since: base-4.9.0.0 |
Foldable (URec Float :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => URec Float m -> m # foldMap :: Monoid m => (a -> m) -> URec Float a -> m # foldr :: (a -> b -> b) -> b -> URec Float a -> b # foldr' :: (a -> b -> b) -> b -> URec Float a -> b # foldl :: (b -> a -> b) -> b -> URec Float a -> b # foldl' :: (b -> a -> b) -> b -> URec Float a -> b # foldr1 :: (a -> a -> a) -> URec Float a -> a # foldl1 :: (a -> a -> a) -> URec Float a -> a # toList :: URec Float a -> [a] # null :: URec Float a -> Bool # length :: URec Float a -> Int # elem :: Eq a => a -> URec Float a -> Bool # maximum :: Ord a => URec Float a -> a # minimum :: Ord a => URec Float a -> a # | |
Traversable (URec Float :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
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) | 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
Eq Decimal # | |
Show Decimal # | |
SimpleType Decimal # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType Decimal # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser Decimal # schemaTypeToXML :: String -> Decimal -> [Content ()] # |
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
Eq Double | Note that due to the presence of
Also note that
|
Floating Double | Since: base-2.1 |
Ord Double | Note that due to the presence of
Also note that, due to the same,
|
Read Double | Since: base-2.1 |
RealFloat Double | Since: base-2.1 |
Defined in GHC.Float Methods 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 | |
Defined in Text.Parse Methods parse :: TextParser Double # parsePrec :: Int -> TextParser Double # parseList :: TextParser [Double] # | |
SimpleType Double # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
HTypeable Double # | |
Defined in Text.XML.HaXml.TypeMapping | |
XmlContent Double # | |
SchemaType Double # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser Double # schemaTypeToXML :: String -> Double -> [Content ()] # | |
Generic1 (URec Double :: k -> Type) | |
Functor (URec Double :: Type -> Type) | Since: base-4.9.0.0 |
Foldable (URec Double :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => URec Double m -> m # foldMap :: Monoid m => (a -> m) -> URec Double a -> m # foldr :: (a -> b -> b) -> b -> URec Double a -> b # foldr' :: (a -> b -> b) -> b -> URec Double a -> b # foldl :: (b -> a -> b) -> b -> URec Double a -> b # foldl' :: (b -> a -> b) -> b -> URec Double a -> b # foldr1 :: (a -> a -> a) -> URec Double a -> a # foldl1 :: (a -> a -> a) -> URec Double a -> a # toList :: URec Double a -> [a] # null :: URec Double a -> Bool # length :: URec Double a -> Int # elem :: Eq a => a -> URec Double a -> Bool # maximum :: Ord a => URec Double a -> a # minimum :: Ord a => URec Double a -> a # | |
Traversable (URec Double :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Eq (URec Double p) | Since: base-4.9.0.0 |
Ord (URec Double p) | Since: base-4.9.0.0 |
Defined in GHC.Generics Methods 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 # | |
Show (URec Double p) | Since: base-4.9.0.0 |
Generic (URec Double p) | |
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
Eq AnyURI # | |
Show AnyURI # | |
SimpleType AnyURI # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType AnyURI # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser AnyURI # schemaTypeToXML :: String -> AnyURI -> [Content ()] # |
A QName is a (possibly) qualified name, in the sense of XML namespaces.
Instances
Eq NOTATION # | |
Show NOTATION # | |
SimpleType NOTATION # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType NOTATION # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser NOTATION # schemaTypeToXML :: String -> NOTATION -> [Content ()] # |
Instances
Eq Duration # | |
Show Duration # | |
SimpleType Duration # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType Duration # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser Duration # schemaTypeToXML :: String -> Duration -> [Content ()] # |
Instances
Eq DateTime # | |
Show DateTime # | |
SimpleType DateTime # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType DateTime # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser DateTime # schemaTypeToXML :: String -> DateTime -> [Content ()] # |
Instances
Eq Time # | |
Show Time # | |
SimpleType Time # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType Time # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser Time # schemaTypeToXML :: String -> Time -> [Content ()] # |
Instances
Eq Date # | |
Show Date # | |
SimpleType Date # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType Date # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser Date # schemaTypeToXML :: String -> Date -> [Content ()] # |
data GYearMonth #
Constructors
GYearMonth String |
Instances
Eq GYearMonth # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
Show GYearMonth # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes Methods showsPrec :: Int -> GYearMonth -> ShowS # show :: GYearMonth -> String # showList :: [GYearMonth] -> ShowS # | |
SimpleType GYearMonth # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType GYearMonth # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser GYearMonth # schemaTypeToXML :: String -> GYearMonth -> [Content ()] # |
Instances
Eq GYear # | |
Show GYear # | |
SimpleType GYear # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType GYear # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser GYear # schemaTypeToXML :: String -> GYear -> [Content ()] # |
Instances
Eq GMonthDay # | |
Show GMonthDay # | |
SimpleType GMonthDay # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType GMonthDay # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser GMonthDay # schemaTypeToXML :: String -> GMonthDay -> [Content ()] # |
Instances
Eq GDay # | |
Show GDay # | |
SimpleType GDay # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType GDay # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser GDay # schemaTypeToXML :: String -> GDay -> [Content ()] # |
Instances
Eq GMonth # | |
Show GMonth # | |
SimpleType GMonth # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType GMonth # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser GMonth # schemaTypeToXML :: String -> GMonth -> [Content ()] # |
Derived, yet builtin, datatypes
newtype NormalizedString #
Constructors
Normalized String |
Instances
Eq NormalizedString # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes Methods (==) :: NormalizedString -> NormalizedString -> Bool # (/=) :: NormalizedString -> NormalizedString -> Bool # | |
Show NormalizedString # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes Methods showsPrec :: Int -> NormalizedString -> ShowS # show :: NormalizedString -> String # showList :: [NormalizedString] -> ShowS # | |
SimpleType NormalizedString # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes Methods | |
SchemaType NormalizedString # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser NormalizedString # schemaTypeToXML :: String -> NormalizedString -> [Content ()] # |
Instances
Eq Token # | |
Show Token # | |
SimpleType Token # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType Token # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser Token # schemaTypeToXML :: String -> Token -> [Content ()] # |
Instances
Eq Language # | |
Show Language # | |
SimpleType Language # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType Language # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser Language # schemaTypeToXML :: String -> Language -> [Content ()] # |
Instances
Eq Name # | |
Show Name # | |
SimpleType Name # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType Name # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser Name # schemaTypeToXML :: String -> Name -> [Content ()] # |
Instances
Eq NCName # | |
Show NCName # | |
SimpleType NCName # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType NCName # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser NCName # schemaTypeToXML :: String -> NCName -> [Content ()] # |
Instances
Eq ID # | |
Show ID # | |
SimpleType ID # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType ID # | |
Defined in Text.XML.HaXml.Schema.Schema |
Instances
Eq IDREF # | |
Show IDREF # | |
SimpleType IDREF # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType IDREF # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser IDREF # schemaTypeToXML :: String -> IDREF -> [Content ()] # |
Instances
Eq IDREFS # | |
Show IDREFS # | |
SimpleType IDREFS # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType IDREFS # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser IDREFS # schemaTypeToXML :: String -> IDREFS -> [Content ()] # |
Instances
Eq ENTITY # | |
Show ENTITY # | |
SimpleType ENTITY # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType ENTITY # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser ENTITY # schemaTypeToXML :: String -> ENTITY -> [Content ()] # |
Instances
Eq ENTITIES # | |
Show ENTITIES # | |
SimpleType ENTITIES # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType ENTITIES # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser ENTITIES # schemaTypeToXML :: String -> ENTITIES -> [Content ()] # |
Instances
Eq NMTOKEN # | |
Show NMTOKEN # | |
SimpleType NMTOKEN # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType NMTOKEN # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser NMTOKEN # schemaTypeToXML :: String -> NMTOKEN -> [Content ()] # |
Instances
Eq NMTOKENS # | |
Show NMTOKENS # | |
SimpleType NMTOKENS # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType NMTOKENS # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser NMTOKENS # schemaTypeToXML :: String -> NMTOKENS -> [Content ()] # |
Invariant: Jn#
and Jp#
are used iff value doesn't fit in S#
Useful properties resulting from the invariants:
Instances
Enum Integer | Since: base-2.1 |
Eq Integer | |
Integral Integer | Since: base-2.0.1 |
Defined in GHC.Real | |
Num Integer | Since: base-2.1 |
Ord Integer | |
Read Integer | Since: base-2.1 |
Real Integer | Since: base-2.0.1 |
Defined in GHC.Real Methods toRational :: Integer -> Rational # | |
Show Integer | Since: base-2.1 |
Ix Integer | Since: base-2.1 |
Defined in GHC.Arr | |
Parse Integer | |
Defined in Text.Parse Methods parse :: TextParser Integer # parsePrec :: Int -> TextParser Integer # parseList :: TextParser [Integer] # | |
SimpleType Integer # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
HTypeable Integer # | |
Defined in Text.XML.HaXml.TypeMapping | |
XmlContent Integer # | |
SchemaType Integer # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser Integer # schemaTypeToXML :: String -> Integer -> [Content ()] # |
newtype NonPositiveInteger #
Instances
Eq NonPositiveInteger # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes Methods (==) :: NonPositiveInteger -> NonPositiveInteger -> Bool # (/=) :: NonPositiveInteger -> NonPositiveInteger -> Bool # | |
Show NonPositiveInteger # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes Methods showsPrec :: Int -> NonPositiveInteger -> ShowS # show :: NonPositiveInteger -> String # showList :: [NonPositiveInteger] -> ShowS # | |
SimpleType NonPositiveInteger # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes Methods | |
SchemaType NonPositiveInteger # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser NonPositiveInteger # schemaTypeToXML :: String -> NonPositiveInteger -> [Content ()] # |
newtype NegativeInteger #
Instances
Eq NegativeInteger # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes Methods (==) :: NegativeInteger -> NegativeInteger -> Bool # (/=) :: NegativeInteger -> NegativeInteger -> Bool # | |
Show NegativeInteger # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes Methods showsPrec :: Int -> NegativeInteger -> ShowS # show :: NegativeInteger -> String # showList :: [NegativeInteger] -> ShowS # | |
SimpleType NegativeInteger # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType NegativeInteger # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser NegativeInteger # schemaTypeToXML :: String -> NegativeInteger -> [Content ()] # |
Instances
Eq Long # | |
Show Long # | |
SimpleType Long # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType Long # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser Long # schemaTypeToXML :: String -> Long -> [Content ()] # |
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
Bounded Int | Since: base-2.1 |
Enum Int | Since: base-2.1 |
Eq Int | |
Integral Int | Since: base-2.0.1 |
Num Int | Since: base-2.1 |
Ord Int | |
Read Int | Since: base-2.1 |
Real Int | Since: base-2.0.1 |
Defined in GHC.Real Methods toRational :: Int -> Rational # | |
Show Int | Since: base-2.1 |
Ix Int | Since: base-2.1 |
Parse Int | |
Defined in Text.Parse | |
SimpleType Int # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
HTypeable Int # | |
Defined in Text.XML.HaXml.TypeMapping | |
XmlContent Int # | |
SchemaType Int # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser Int # schemaTypeToXML :: String -> Int -> [Content ()] # | |
Generic1 (URec Int :: k -> Type) | |
Functor (URec Int :: Type -> Type) | Since: base-4.9.0.0 |
Foldable (URec Int :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => URec Int m -> m # foldMap :: Monoid m => (a -> m) -> URec Int a -> m # foldr :: (a -> b -> b) -> b -> URec Int a -> b # foldr' :: (a -> b -> b) -> b -> URec Int a -> b # foldl :: (b -> a -> b) -> b -> URec Int a -> b # foldl' :: (b -> a -> b) -> b -> URec Int a -> b # foldr1 :: (a -> a -> a) -> URec Int a -> a # foldl1 :: (a -> a -> a) -> URec Int a -> a # elem :: Eq a => a -> URec Int a -> Bool # maximum :: Ord a => URec Int a -> a # minimum :: Ord a => URec Int a -> a # | |
Traversable (URec Int :: Type -> Type) | 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 |
Show (URec Int p) | Since: base-4.9.0.0 |
Generic (URec Int p) | |
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
Eq Short # | |
Show Short # | |
SimpleType Short # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType Short # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser Short # schemaTypeToXML :: String -> Short -> [Content ()] # |
Instances
Eq Byte # | |
Show Byte # | |
SimpleType Byte # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType Byte # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser Byte # schemaTypeToXML :: String -> Byte -> [Content ()] # |
newtype NonNegativeInteger #
Instances
Eq NonNegativeInteger # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes Methods (==) :: NonNegativeInteger -> NonNegativeInteger -> Bool # (/=) :: NonNegativeInteger -> NonNegativeInteger -> Bool # | |
Show NonNegativeInteger # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes Methods showsPrec :: Int -> NonNegativeInteger -> ShowS # show :: NonNegativeInteger -> String # showList :: [NonNegativeInteger] -> ShowS # | |
SimpleType NonNegativeInteger # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes Methods | |
SchemaType NonNegativeInteger # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser NonNegativeInteger # schemaTypeToXML :: String -> NonNegativeInteger -> [Content ()] # |
newtype UnsignedLong #
Instances
Eq UnsignedLong # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
Show UnsignedLong # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes Methods showsPrec :: Int -> UnsignedLong -> ShowS # show :: UnsignedLong -> String # showList :: [UnsignedLong] -> ShowS # | |
SimpleType UnsignedLong # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType UnsignedLong # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser UnsignedLong # schemaTypeToXML :: String -> UnsignedLong -> [Content ()] # |
newtype UnsignedInt #
Instances
Eq UnsignedInt # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
Show UnsignedInt # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes Methods showsPrec :: Int -> UnsignedInt -> ShowS # show :: UnsignedInt -> String # showList :: [UnsignedInt] -> ShowS # | |
SimpleType UnsignedInt # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType UnsignedInt # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser UnsignedInt # schemaTypeToXML :: String -> UnsignedInt -> [Content ()] # |
newtype UnsignedShort #
Instances
Eq UnsignedShort # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes Methods (==) :: UnsignedShort -> UnsignedShort -> Bool # (/=) :: UnsignedShort -> UnsignedShort -> Bool # | |
Show UnsignedShort # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes Methods showsPrec :: Int -> UnsignedShort -> ShowS # show :: UnsignedShort -> String # showList :: [UnsignedShort] -> ShowS # | |
SimpleType UnsignedShort # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType UnsignedShort # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser UnsignedShort # schemaTypeToXML :: String -> UnsignedShort -> [Content ()] # |
newtype UnsignedByte #
Instances
Eq UnsignedByte # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
Show UnsignedByte # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes Methods showsPrec :: Int -> UnsignedByte -> ShowS # show :: UnsignedByte -> String # showList :: [UnsignedByte] -> ShowS # | |
SimpleType UnsignedByte # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType UnsignedByte # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser UnsignedByte # schemaTypeToXML :: String -> UnsignedByte -> [Content ()] # |
newtype PositiveInteger #
Instances
Eq PositiveInteger # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes Methods (==) :: PositiveInteger -> PositiveInteger -> Bool # (/=) :: PositiveInteger -> PositiveInteger -> Bool # | |
Show PositiveInteger # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes Methods showsPrec :: Int -> PositiveInteger -> ShowS # show :: PositiveInteger -> String # showList :: [PositiveInteger] -> ShowS # | |
SimpleType PositiveInteger # | |
Defined in Text.XML.HaXml.Schema.PrimitiveTypes | |
SchemaType PositiveInteger # | |
Defined in Text.XML.HaXml.Schema.Schema Methods parseSchemaType :: String -> XMLParser PositiveInteger # schemaTypeToXML :: String -> PositiveInteger -> [Content ()] # |