{-# LANGUAGE TypeSynonymInstances #-}
module Text.XML.HaXml.Schema.PrimitiveTypes
(
SimpleType(..)
, module Text.Parse
,
XsdString(..)
, Boolean(..)
, Base64Binary(..)
, HexBinary(..)
, Float(..)
, Decimal(..)
, Double(..)
, AnyURI(..)
, QName(..)
, NOTATION(..)
, Duration(..)
, DateTime(..)
, Time(..)
, Date(..)
, GYearMonth(..)
, GYear(..)
, GMonthDay(..)
, GDay(..)
, GMonth(..)
,
NormalizedString(..)
, Token(..)
, Language(..)
, Name(..)
, NCName(..)
, ID(..)
, IDREF(..)
, IDREFS(..)
, ENTITY(..)
, ENTITIES(..)
, NMTOKEN(..)
, NMTOKENS(..)
, Integer(..)
, NonPositiveInteger(..)
, NegativeInteger(..)
, Long(..)
, Int(..)
, Short(..)
, Byte(..)
, NonNegativeInteger(..)
, UnsignedLong(..)
, UnsignedInt(..)
, UnsignedShort(..)
, UnsignedByte(..)
, PositiveInteger(..)
) where
import Text.Parse
import Data.Char as Char
import Text.XML.HaXml.Types (QName(..))
import Data.Int
import Data.Word
class SimpleType a where
acceptingParser :: TextParser a
simpleTypeText :: a -> String
type Boolean = Bool
newtype XsdString = XsdString String deriving (XsdString -> XsdString -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: XsdString -> XsdString -> Bool
$c/= :: XsdString -> XsdString -> Bool
== :: XsdString -> XsdString -> Bool
$c== :: XsdString -> XsdString -> Bool
Eq,Int -> XsdString -> ShowS
[XsdString] -> ShowS
XsdString -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [XsdString] -> ShowS
$cshowList :: [XsdString] -> ShowS
show :: XsdString -> String
$cshow :: XsdString -> String
showsPrec :: Int -> XsdString -> ShowS
$cshowsPrec :: Int -> XsdString -> ShowS
Show)
data Base64Binary = Base64Binary String deriving (Base64Binary -> Base64Binary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Base64Binary -> Base64Binary -> Bool
$c/= :: Base64Binary -> Base64Binary -> Bool
== :: Base64Binary -> Base64Binary -> Bool
$c== :: Base64Binary -> Base64Binary -> Bool
Eq,Int -> Base64Binary -> ShowS
[Base64Binary] -> ShowS
Base64Binary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Base64Binary] -> ShowS
$cshowList :: [Base64Binary] -> ShowS
show :: Base64Binary -> String
$cshow :: Base64Binary -> String
showsPrec :: Int -> Base64Binary -> ShowS
$cshowsPrec :: Int -> Base64Binary -> ShowS
Show)
data HexBinary = HexBinary String deriving (HexBinary -> HexBinary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HexBinary -> HexBinary -> Bool
$c/= :: HexBinary -> HexBinary -> Bool
== :: HexBinary -> HexBinary -> Bool
$c== :: HexBinary -> HexBinary -> Bool
Eq,Int -> HexBinary -> ShowS
[HexBinary] -> ShowS
HexBinary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HexBinary] -> ShowS
$cshowList :: [HexBinary] -> ShowS
show :: HexBinary -> String
$cshow :: HexBinary -> String
showsPrec :: Int -> HexBinary -> ShowS
$cshowsPrec :: Int -> HexBinary -> ShowS
Show)
data AnyURI = AnyURI String deriving (AnyURI -> AnyURI -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnyURI -> AnyURI -> Bool
$c/= :: AnyURI -> AnyURI -> Bool
== :: AnyURI -> AnyURI -> Bool
$c== :: AnyURI -> AnyURI -> Bool
Eq,Int -> AnyURI -> ShowS
[AnyURI] -> ShowS
AnyURI -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AnyURI] -> ShowS
$cshowList :: [AnyURI] -> ShowS
show :: AnyURI -> String
$cshow :: AnyURI -> String
showsPrec :: Int -> AnyURI -> ShowS
$cshowsPrec :: Int -> AnyURI -> ShowS
Show)
data NOTATION = NOTATION String
deriving (NOTATION -> NOTATION -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NOTATION -> NOTATION -> Bool
$c/= :: NOTATION -> NOTATION -> Bool
== :: NOTATION -> NOTATION -> Bool
$c== :: NOTATION -> NOTATION -> Bool
Eq,Int -> NOTATION -> ShowS
[NOTATION] -> ShowS
NOTATION -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NOTATION] -> ShowS
$cshowList :: [NOTATION] -> ShowS
show :: NOTATION -> String
$cshow :: NOTATION -> String
showsPrec :: Int -> NOTATION -> ShowS
$cshowsPrec :: Int -> NOTATION -> ShowS
Show)
data Decimal = Decimal Double deriving (Decimal -> Decimal -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Decimal -> Decimal -> Bool
$c/= :: Decimal -> Decimal -> Bool
== :: Decimal -> Decimal -> Bool
$c== :: Decimal -> Decimal -> Bool
Eq,Int -> Decimal -> ShowS
[Decimal] -> ShowS
Decimal -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Decimal] -> ShowS
$cshowList :: [Decimal] -> ShowS
show :: Decimal -> String
$cshow :: Decimal -> String
showsPrec :: Int -> Decimal -> ShowS
$cshowsPrec :: Int -> Decimal -> ShowS
Show)
data Duration = Duration Bool Int Int Int Int Int Float deriving (Duration -> Duration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Duration -> Duration -> Bool
$c/= :: Duration -> Duration -> Bool
== :: Duration -> Duration -> Bool
$c== :: Duration -> Duration -> Bool
Eq,Int -> Duration -> ShowS
[Duration] -> ShowS
Duration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Duration] -> ShowS
$cshowList :: [Duration] -> ShowS
show :: Duration -> String
$cshow :: Duration -> String
showsPrec :: Int -> Duration -> ShowS
$cshowsPrec :: Int -> Duration -> ShowS
Show)
data DateTime = DateTime String deriving (DateTime -> DateTime -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DateTime -> DateTime -> Bool
$c/= :: DateTime -> DateTime -> Bool
== :: DateTime -> DateTime -> Bool
$c== :: DateTime -> DateTime -> Bool
Eq,Int -> DateTime -> ShowS
[DateTime] -> ShowS
DateTime -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DateTime] -> ShowS
$cshowList :: [DateTime] -> ShowS
show :: DateTime -> String
$cshow :: DateTime -> String
showsPrec :: Int -> DateTime -> ShowS
$cshowsPrec :: Int -> DateTime -> ShowS
Show)
data Time = Time String deriving (Time -> Time -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Time -> Time -> Bool
$c/= :: Time -> Time -> Bool
== :: Time -> Time -> Bool
$c== :: Time -> Time -> Bool
Eq,Int -> Time -> ShowS
[Time] -> ShowS
Time -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Time] -> ShowS
$cshowList :: [Time] -> ShowS
show :: Time -> String
$cshow :: Time -> String
showsPrec :: Int -> Time -> ShowS
$cshowsPrec :: Int -> Time -> ShowS
Show)
data Date = Date String deriving (Date -> Date -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Date -> Date -> Bool
$c/= :: Date -> Date -> Bool
== :: Date -> Date -> Bool
$c== :: Date -> Date -> Bool
Eq,Int -> Date -> ShowS
[Date] -> ShowS
Date -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Date] -> ShowS
$cshowList :: [Date] -> ShowS
show :: Date -> String
$cshow :: Date -> String
showsPrec :: Int -> Date -> ShowS
$cshowsPrec :: Int -> Date -> ShowS
Show)
data GYearMonth = GYearMonth String deriving (GYearMonth -> GYearMonth -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GYearMonth -> GYearMonth -> Bool
$c/= :: GYearMonth -> GYearMonth -> Bool
== :: GYearMonth -> GYearMonth -> Bool
$c== :: GYearMonth -> GYearMonth -> Bool
Eq,Int -> GYearMonth -> ShowS
[GYearMonth] -> ShowS
GYearMonth -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GYearMonth] -> ShowS
$cshowList :: [GYearMonth] -> ShowS
show :: GYearMonth -> String
$cshow :: GYearMonth -> String
showsPrec :: Int -> GYearMonth -> ShowS
$cshowsPrec :: Int -> GYearMonth -> ShowS
Show)
data GYear = GYear String deriving (GYear -> GYear -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GYear -> GYear -> Bool
$c/= :: GYear -> GYear -> Bool
== :: GYear -> GYear -> Bool
$c== :: GYear -> GYear -> Bool
Eq,Int -> GYear -> ShowS
[GYear] -> ShowS
GYear -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GYear] -> ShowS
$cshowList :: [GYear] -> ShowS
show :: GYear -> String
$cshow :: GYear -> String
showsPrec :: Int -> GYear -> ShowS
$cshowsPrec :: Int -> GYear -> ShowS
Show)
data GMonthDay = GMonthDay String deriving (GMonthDay -> GMonthDay -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GMonthDay -> GMonthDay -> Bool
$c/= :: GMonthDay -> GMonthDay -> Bool
== :: GMonthDay -> GMonthDay -> Bool
$c== :: GMonthDay -> GMonthDay -> Bool
Eq,Int -> GMonthDay -> ShowS
[GMonthDay] -> ShowS
GMonthDay -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GMonthDay] -> ShowS
$cshowList :: [GMonthDay] -> ShowS
show :: GMonthDay -> String
$cshow :: GMonthDay -> String
showsPrec :: Int -> GMonthDay -> ShowS
$cshowsPrec :: Int -> GMonthDay -> ShowS
Show)
data GDay = GDay String deriving (GDay -> GDay -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GDay -> GDay -> Bool
$c/= :: GDay -> GDay -> Bool
== :: GDay -> GDay -> Bool
$c== :: GDay -> GDay -> Bool
Eq,Int -> GDay -> ShowS
[GDay] -> ShowS
GDay -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GDay] -> ShowS
$cshowList :: [GDay] -> ShowS
show :: GDay -> String
$cshow :: GDay -> String
showsPrec :: Int -> GDay -> ShowS
$cshowsPrec :: Int -> GDay -> ShowS
Show)
data GMonth = GMonth String deriving (GMonth -> GMonth -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GMonth -> GMonth -> Bool
$c/= :: GMonth -> GMonth -> Bool
== :: GMonth -> GMonth -> Bool
$c== :: GMonth -> GMonth -> Bool
Eq,Int -> GMonth -> ShowS
[GMonth] -> ShowS
GMonth -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GMonth] -> ShowS
$cshowList :: [GMonth] -> ShowS
show :: GMonth -> String
$cshow :: GMonth -> String
showsPrec :: Int -> GMonth -> ShowS
$cshowsPrec :: Int -> GMonth -> ShowS
Show)
isNext :: Char -> TextParser Char
isNext :: Char -> TextParser Char
isNext Char
c = do Char
d <- forall t. Parser t t
next
if Char
cforall a. Eq a => a -> a -> Bool
==Char
d then forall (m :: * -> *) a. Monad m => a -> m a
return Char
c else forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"expected "forall a. [a] -> [a] -> [a]
++Char
cforall a. a -> [a] -> [a]
:String
", got "forall a. [a] -> [a] -> [a]
++Char
dforall a. a -> [a] -> [a]
:String
".")
instance SimpleType Bool where
acceptingParser :: TextParser Bool
acceptingParser = do String
w <- TextParser String
word
case String
w of String
"true" -> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True;
String
"false" -> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
String
"0" -> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False;
String
"1" -> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
String
_ -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"Not a bool: "forall a. [a] -> [a] -> [a]
++String
w)
simpleTypeText :: Bool -> String
simpleTypeText Bool
False = String
"false"
simpleTypeText Bool
True = String
"true"
instance SimpleType XsdString where
acceptingParser :: TextParser XsdString
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> XsdString
XsdString (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: XsdString -> String
simpleTypeText (XsdString String
s) = String
s
instance SimpleType Base64Binary where
acceptingParser :: TextParser Base64Binary
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Base64Binary
Base64Binary (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (forall t. (t -> Bool) -> Parser t t
satisfy Char -> Bool
isAlphaNum forall t a. Parser t a -> Parser t a -> Parser t a
`onFail`
forall t. (t -> Bool) -> Parser t t
satisfy Char -> Bool
isSpace forall t a. Parser t a -> Parser t a -> Parser t a
`onFail`
forall t. (t -> Bool) -> Parser t t
satisfy (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem`String
"+/=")))
simpleTypeText :: Base64Binary -> String
simpleTypeText (Base64Binary String
s) = String
s
instance SimpleType HexBinary where
acceptingParser :: TextParser HexBinary
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> HexBinary
HexBinary (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (forall t. (t -> Bool) -> Parser t t
satisfy Char -> Bool
Char.isHexDigit))
simpleTypeText :: HexBinary -> String
simpleTypeText (HexBinary String
s) = String
s
instance SimpleType AnyURI where
acceptingParser :: TextParser AnyURI
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> AnyURI
AnyURI (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: AnyURI -> String
simpleTypeText (AnyURI String
s) = String
s
instance SimpleType NOTATION where
acceptingParser :: TextParser NOTATION
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> NOTATION
NOTATION (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: NOTATION -> String
simpleTypeText (NOTATION String
s) = String
s
instance SimpleType Decimal where
acceptingParser :: TextParser Decimal
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Double -> Decimal
Decimal forall a. Parse a => TextParser a
parse
simpleTypeText :: Decimal -> String
simpleTypeText (Decimal Double
s) = forall a. Show a => a -> String
show Double
s
instance SimpleType Float where
acceptingParser :: TextParser Float
acceptingParser = forall a. Parse a => TextParser a
parse
simpleTypeText :: Float -> String
simpleTypeText Float
x = forall a. Show a => a -> String
show Float
x
instance SimpleType Double where
acceptingParser :: TextParser Double
acceptingParser = forall a. Parse a => TextParser a
parse
simpleTypeText :: Double -> String
simpleTypeText Double
x = forall a. Show a => a -> String
show Double
x
instance SimpleType Duration where
acceptingParser :: TextParser Duration
acceptingParser = forall (m :: * -> *) a. Monad m => a -> m a
return Bool -> Int -> Int -> Int -> Int -> Int -> Float -> Duration
Duration forall (p :: * -> *) a b. PolyParse p => p (a -> b) -> p a -> p b
`apply` (do Char -> TextParser Char
isNext Char
'-'; forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
forall t a. Parser t a -> Parser t a -> Parser t a
`onFail` forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True)
forall (p :: * -> *) a b. PolyParse p => p a -> p b -> p a
`discard` Char -> TextParser Char
isNext Char
'P'
forall (p :: * -> *) a b. PolyParse p => p (a -> b) -> p a -> p b
`apply` ((forall a. Integral a => TextParser a
parseDec forall (p :: * -> *) a b. PolyParse p => p a -> p b -> p a
`discard` Char -> TextParser Char
isNext Char
'Y')
forall t a. Parser t a -> Parser t a -> Parser t a
`onFail` forall (m :: * -> *) a. Monad m => a -> m a
return Int
0)
forall (p :: * -> *) a b. PolyParse p => p (a -> b) -> p a -> p b
`apply` ((forall a. Integral a => TextParser a
parseDec forall (p :: * -> *) a b. PolyParse p => p a -> p b -> p a
`discard` Char -> TextParser Char
isNext Char
'M')
forall t a. Parser t a -> Parser t a -> Parser t a
`onFail` forall (m :: * -> *) a. Monad m => a -> m a
return Int
0)
forall (p :: * -> *) a b. PolyParse p => p (a -> b) -> p a -> p b
`apply` ((forall a. Integral a => TextParser a
parseDec forall (p :: * -> *) a b. PolyParse p => p a -> p b -> p a
`discard` Char -> TextParser Char
isNext Char
'D')
forall t a. Parser t a -> Parser t a -> Parser t a
`onFail` forall (m :: * -> *) a. Monad m => a -> m a
return Int
0)
forall (p :: * -> *) a b. PolyParse p => p a -> p b -> p a
`discard` (Char -> TextParser Char
isNext Char
'T'forall t a. Parser t a -> Parser t a -> Parser t a
`onFail`forall (m :: * -> *) a. Monad m => a -> m a
return Char
'T')
forall (p :: * -> *) a b. PolyParse p => p (a -> b) -> p a -> p b
`apply` ((forall a. Integral a => TextParser a
parseDec forall (p :: * -> *) a b. PolyParse p => p a -> p b -> p a
`discard` Char -> TextParser Char
isNext Char
'H')
forall t a. Parser t a -> Parser t a -> Parser t a
`onFail` forall (m :: * -> *) a. Monad m => a -> m a
return Int
0)
forall (p :: * -> *) a b. PolyParse p => p (a -> b) -> p a -> p b
`apply` ((forall a. Integral a => TextParser a
parseDec forall (p :: * -> *) a b. PolyParse p => p a -> p b -> p a
`discard` Char -> TextParser Char
isNext Char
'M')
forall t a. Parser t a -> Parser t a -> Parser t a
`onFail` forall (m :: * -> *) a. Monad m => a -> m a
return Int
0)
forall (p :: * -> *) a b. PolyParse p => p (a -> b) -> p a -> p b
`apply` ((forall a. RealFrac a => TextParser a
parseFloat forall (p :: * -> *) a b. PolyParse p => p a -> p b -> p a
`discard` Char -> TextParser Char
isNext Char
'S')
forall t a. Parser t a -> Parser t a -> Parser t a
`onFail` forall (m :: * -> *) a. Monad m => a -> m a
return Float
0)
simpleTypeText :: Duration -> String
simpleTypeText (Duration Bool
pos Int
0 Int
0 Int
0 Int
0 Int
0 Float
0) = (if Bool
pos then String
"" else String
"-")forall a. [a] -> [a] -> [a]
++String
"P0S"
simpleTypeText (Duration Bool
pos Int
y Int
m Int
d Int
h Int
n Float
s) =
(if Bool
pos then String
"" else String
"-")forall a. [a] -> [a] -> [a]
++String
"P"forall a. [a] -> [a] -> [a]
++forall a. (Num a, Eq a, Show a) => a -> Char -> String
showUnit Int
y Char
'Y'forall a. [a] -> [a] -> [a]
++forall a. (Num a, Eq a, Show a) => a -> Char -> String
showUnit Int
m Char
'M'forall a. [a] -> [a] -> [a]
++forall a. (Num a, Eq a, Show a) => a -> Char -> String
showUnit Int
d Char
'D'forall a. [a] -> [a] -> [a]
++String
showTime
where
showUnit :: (Num a,Eq a,Show a) => a -> Char -> String
showUnit :: forall a. (Num a, Eq a, Show a) => a -> Char -> String
showUnit a
n Char
u = if a
n forall a. Eq a => a -> a -> Bool
== a
0 then String
"" else forall a. Show a => a -> String
show a
n forall a. [a] -> [a] -> [a]
++ [Char
u]
showTime :: String
showTime = if (Int
h,Int
n,Float
s) forall a. Eq a => a -> a -> Bool
== (Int
0,Int
0,Float
0) then String
"" else String
"T"forall a. [a] -> [a] -> [a]
++forall a. (Num a, Eq a, Show a) => a -> Char -> String
showUnit Int
h Char
'H'forall a. [a] -> [a] -> [a]
++forall a. (Num a, Eq a, Show a) => a -> Char -> String
showUnit Int
n Char
'M'forall a. [a] -> [a] -> [a]
++forall a. (Num a, Eq a, Show a) => a -> Char -> String
showUnit Float
s Char
'S'
instance SimpleType DateTime where
acceptingParser :: TextParser DateTime
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> DateTime
DateTime (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: DateTime -> String
simpleTypeText (DateTime String
x) = String
x
instance SimpleType Time where
acceptingParser :: TextParser Time
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Time
Time (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: Time -> String
simpleTypeText (Time String
x) = String
x
instance SimpleType Date where
acceptingParser :: TextParser Date
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Date
Date (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: Date -> String
simpleTypeText (Date String
x) = String
x
instance SimpleType GYearMonth where
acceptingParser :: TextParser GYearMonth
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> GYearMonth
GYearMonth (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: GYearMonth -> String
simpleTypeText (GYearMonth String
x) = String
x
instance SimpleType GYear where
acceptingParser :: TextParser GYear
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> GYear
GYear (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: GYear -> String
simpleTypeText (GYear String
x) = String
x
instance SimpleType GMonthDay where
acceptingParser :: TextParser GMonthDay
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> GMonthDay
GMonthDay (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: GMonthDay -> String
simpleTypeText (GMonthDay String
x) = String
x
instance SimpleType GDay where
acceptingParser :: TextParser GDay
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> GDay
GDay (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: GDay -> String
simpleTypeText (GDay String
x) = String
x
instance SimpleType GMonth where
acceptingParser :: TextParser GMonth
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> GMonth
GMonth (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: GMonth -> String
simpleTypeText (GMonth String
x) = String
x
newtype NormalizedString = Normalized String deriving (NormalizedString -> NormalizedString -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NormalizedString -> NormalizedString -> Bool
$c/= :: NormalizedString -> NormalizedString -> Bool
== :: NormalizedString -> NormalizedString -> Bool
$c== :: NormalizedString -> NormalizedString -> Bool
Eq,Int -> NormalizedString -> ShowS
[NormalizedString] -> ShowS
NormalizedString -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NormalizedString] -> ShowS
$cshowList :: [NormalizedString] -> ShowS
show :: NormalizedString -> String
$cshow :: NormalizedString -> String
showsPrec :: Int -> NormalizedString -> ShowS
$cshowsPrec :: Int -> NormalizedString -> ShowS
Show)
newtype Token = Token String deriving (Token -> Token -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Token -> Token -> Bool
$c/= :: Token -> Token -> Bool
== :: Token -> Token -> Bool
$c== :: Token -> Token -> Bool
Eq,Int -> Token -> ShowS
[Token] -> ShowS
Token -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Token] -> ShowS
$cshowList :: [Token] -> ShowS
show :: Token -> String
$cshow :: Token -> String
showsPrec :: Int -> Token -> ShowS
$cshowsPrec :: Int -> Token -> ShowS
Show)
newtype Language = Language String deriving (Language -> Language -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Language -> Language -> Bool
$c/= :: Language -> Language -> Bool
== :: Language -> Language -> Bool
$c== :: Language -> Language -> Bool
Eq,Int -> Language -> ShowS
[Language] -> ShowS
Language -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Language] -> ShowS
$cshowList :: [Language] -> ShowS
show :: Language -> String
$cshow :: Language -> String
showsPrec :: Int -> Language -> ShowS
$cshowsPrec :: Int -> Language -> ShowS
Show)
newtype Name = Name String deriving (Name -> Name -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Name -> Name -> Bool
$c/= :: Name -> Name -> Bool
== :: Name -> Name -> Bool
$c== :: Name -> Name -> Bool
Eq,Int -> Name -> ShowS
[Name] -> ShowS
Name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Name] -> ShowS
$cshowList :: [Name] -> ShowS
show :: Name -> String
$cshow :: Name -> String
showsPrec :: Int -> Name -> ShowS
$cshowsPrec :: Int -> Name -> ShowS
Show)
newtype NCName = NCName String deriving (NCName -> NCName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NCName -> NCName -> Bool
$c/= :: NCName -> NCName -> Bool
== :: NCName -> NCName -> Bool
$c== :: NCName -> NCName -> Bool
Eq,Int -> NCName -> ShowS
[NCName] -> ShowS
NCName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NCName] -> ShowS
$cshowList :: [NCName] -> ShowS
show :: NCName -> String
$cshow :: NCName -> String
showsPrec :: Int -> NCName -> ShowS
$cshowsPrec :: Int -> NCName -> ShowS
Show)
newtype ID = ID String deriving (ID -> ID -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ID -> ID -> Bool
$c/= :: ID -> ID -> Bool
== :: ID -> ID -> Bool
$c== :: ID -> ID -> Bool
Eq,Int -> ID -> ShowS
[ID] -> ShowS
ID -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ID] -> ShowS
$cshowList :: [ID] -> ShowS
show :: ID -> String
$cshow :: ID -> String
showsPrec :: Int -> ID -> ShowS
$cshowsPrec :: Int -> ID -> ShowS
Show)
newtype IDREF = IDREF String deriving (IDREF -> IDREF -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IDREF -> IDREF -> Bool
$c/= :: IDREF -> IDREF -> Bool
== :: IDREF -> IDREF -> Bool
$c== :: IDREF -> IDREF -> Bool
Eq,Int -> IDREF -> ShowS
[IDREF] -> ShowS
IDREF -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IDREF] -> ShowS
$cshowList :: [IDREF] -> ShowS
show :: IDREF -> String
$cshow :: IDREF -> String
showsPrec :: Int -> IDREF -> ShowS
$cshowsPrec :: Int -> IDREF -> ShowS
Show)
newtype IDREFS = IDREFS String deriving (IDREFS -> IDREFS -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IDREFS -> IDREFS -> Bool
$c/= :: IDREFS -> IDREFS -> Bool
== :: IDREFS -> IDREFS -> Bool
$c== :: IDREFS -> IDREFS -> Bool
Eq,Int -> IDREFS -> ShowS
[IDREFS] -> ShowS
IDREFS -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IDREFS] -> ShowS
$cshowList :: [IDREFS] -> ShowS
show :: IDREFS -> String
$cshow :: IDREFS -> String
showsPrec :: Int -> IDREFS -> ShowS
$cshowsPrec :: Int -> IDREFS -> ShowS
Show)
newtype ENTITY = ENTITY String deriving (ENTITY -> ENTITY -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ENTITY -> ENTITY -> Bool
$c/= :: ENTITY -> ENTITY -> Bool
== :: ENTITY -> ENTITY -> Bool
$c== :: ENTITY -> ENTITY -> Bool
Eq,Int -> ENTITY -> ShowS
[ENTITY] -> ShowS
ENTITY -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ENTITY] -> ShowS
$cshowList :: [ENTITY] -> ShowS
show :: ENTITY -> String
$cshow :: ENTITY -> String
showsPrec :: Int -> ENTITY -> ShowS
$cshowsPrec :: Int -> ENTITY -> ShowS
Show)
newtype ENTITIES = ENTITIES String deriving (ENTITIES -> ENTITIES -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ENTITIES -> ENTITIES -> Bool
$c/= :: ENTITIES -> ENTITIES -> Bool
== :: ENTITIES -> ENTITIES -> Bool
$c== :: ENTITIES -> ENTITIES -> Bool
Eq,Int -> ENTITIES -> ShowS
[ENTITIES] -> ShowS
ENTITIES -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ENTITIES] -> ShowS
$cshowList :: [ENTITIES] -> ShowS
show :: ENTITIES -> String
$cshow :: ENTITIES -> String
showsPrec :: Int -> ENTITIES -> ShowS
$cshowsPrec :: Int -> ENTITIES -> ShowS
Show)
newtype NMTOKEN = NMTOKEN String deriving (NMTOKEN -> NMTOKEN -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NMTOKEN -> NMTOKEN -> Bool
$c/= :: NMTOKEN -> NMTOKEN -> Bool
== :: NMTOKEN -> NMTOKEN -> Bool
$c== :: NMTOKEN -> NMTOKEN -> Bool
Eq,Int -> NMTOKEN -> ShowS
[NMTOKEN] -> ShowS
NMTOKEN -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NMTOKEN] -> ShowS
$cshowList :: [NMTOKEN] -> ShowS
show :: NMTOKEN -> String
$cshow :: NMTOKEN -> String
showsPrec :: Int -> NMTOKEN -> ShowS
$cshowsPrec :: Int -> NMTOKEN -> ShowS
Show)
newtype NMTOKENS = NMTOKENS String deriving (NMTOKENS -> NMTOKENS -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NMTOKENS -> NMTOKENS -> Bool
$c/= :: NMTOKENS -> NMTOKENS -> Bool
== :: NMTOKENS -> NMTOKENS -> Bool
$c== :: NMTOKENS -> NMTOKENS -> Bool
Eq,Int -> NMTOKENS -> ShowS
[NMTOKENS] -> ShowS
NMTOKENS -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NMTOKENS] -> ShowS
$cshowList :: [NMTOKENS] -> ShowS
show :: NMTOKENS -> String
$cshow :: NMTOKENS -> String
showsPrec :: Int -> NMTOKENS -> ShowS
$cshowsPrec :: Int -> NMTOKENS -> ShowS
Show)
instance SimpleType NormalizedString where
acceptingParser :: TextParser NormalizedString
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> NormalizedString
Normalized (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: NormalizedString -> String
simpleTypeText (Normalized String
x) = String
x
instance SimpleType Token where
acceptingParser :: TextParser Token
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Token
Token (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: Token -> String
simpleTypeText (Token String
x) = String
x
instance SimpleType Language where
acceptingParser :: TextParser Language
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Language
Language (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: Language -> String
simpleTypeText (Language String
x) = String
x
instance SimpleType Name where
acceptingParser :: TextParser Name
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Name
Name (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: Name -> String
simpleTypeText (Name String
x) = String
x
instance SimpleType NCName where
acceptingParser :: TextParser NCName
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> NCName
NCName (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: NCName -> String
simpleTypeText (NCName String
x) = String
x
instance SimpleType ID where
acceptingParser :: TextParser ID
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> ID
ID (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: ID -> String
simpleTypeText (ID String
x) = String
x
instance SimpleType IDREF where
acceptingParser :: TextParser IDREF
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> IDREF
IDREF (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: IDREF -> String
simpleTypeText (IDREF String
x) = String
x
instance SimpleType IDREFS where
acceptingParser :: TextParser IDREFS
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> IDREFS
IDREFS (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: IDREFS -> String
simpleTypeText (IDREFS String
x) = String
x
instance SimpleType ENTITY where
acceptingParser :: TextParser ENTITY
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> ENTITY
ENTITY (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: ENTITY -> String
simpleTypeText (ENTITY String
x) = String
x
instance SimpleType ENTITIES where
acceptingParser :: TextParser ENTITIES
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> ENTITIES
ENTITIES (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: ENTITIES -> String
simpleTypeText (ENTITIES String
x) = String
x
instance SimpleType NMTOKEN where
acceptingParser :: TextParser NMTOKEN
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> NMTOKEN
NMTOKEN (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: NMTOKEN -> String
simpleTypeText (NMTOKEN String
x) = String
x
instance SimpleType NMTOKENS where
acceptingParser :: TextParser NMTOKENS
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> NMTOKENS
NMTOKENS (forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall t. Parser t t
next)
simpleTypeText :: NMTOKENS -> String
simpleTypeText (NMTOKENS String
x) = String
x
newtype NonPositiveInteger = NonPos Integer deriving (NonPositiveInteger -> NonPositiveInteger -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NonPositiveInteger -> NonPositiveInteger -> Bool
$c/= :: NonPositiveInteger -> NonPositiveInteger -> Bool
== :: NonPositiveInteger -> NonPositiveInteger -> Bool
$c== :: NonPositiveInteger -> NonPositiveInteger -> Bool
Eq,Int -> NonPositiveInteger -> ShowS
[NonPositiveInteger] -> ShowS
NonPositiveInteger -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NonPositiveInteger] -> ShowS
$cshowList :: [NonPositiveInteger] -> ShowS
show :: NonPositiveInteger -> String
$cshow :: NonPositiveInteger -> String
showsPrec :: Int -> NonPositiveInteger -> ShowS
$cshowsPrec :: Int -> NonPositiveInteger -> ShowS
Show)
newtype NegativeInteger = Negative Integer deriving (NegativeInteger -> NegativeInteger -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NegativeInteger -> NegativeInteger -> Bool
$c/= :: NegativeInteger -> NegativeInteger -> Bool
== :: NegativeInteger -> NegativeInteger -> Bool
$c== :: NegativeInteger -> NegativeInteger -> Bool
Eq,Int -> NegativeInteger -> ShowS
[NegativeInteger] -> ShowS
NegativeInteger -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NegativeInteger] -> ShowS
$cshowList :: [NegativeInteger] -> ShowS
show :: NegativeInteger -> String
$cshow :: NegativeInteger -> String
showsPrec :: Int -> NegativeInteger -> ShowS
$cshowsPrec :: Int -> NegativeInteger -> ShowS
Show)
newtype Long = Long Int64 deriving (Long -> Long -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Long -> Long -> Bool
$c/= :: Long -> Long -> Bool
== :: Long -> Long -> Bool
$c== :: Long -> Long -> Bool
Eq,Int -> Long -> ShowS
[Long] -> ShowS
Long -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Long] -> ShowS
$cshowList :: [Long] -> ShowS
show :: Long -> String
$cshow :: Long -> String
showsPrec :: Int -> Long -> ShowS
$cshowsPrec :: Int -> Long -> ShowS
Show)
newtype Short = Short Int16 deriving (Short -> Short -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Short -> Short -> Bool
$c/= :: Short -> Short -> Bool
== :: Short -> Short -> Bool
$c== :: Short -> Short -> Bool
Eq,Int -> Short -> ShowS
[Short] -> ShowS
Short -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Short] -> ShowS
$cshowList :: [Short] -> ShowS
show :: Short -> String
$cshow :: Short -> String
showsPrec :: Int -> Short -> ShowS
$cshowsPrec :: Int -> Short -> ShowS
Show)
newtype Byte = Byte Int8 deriving (Byte -> Byte -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Byte -> Byte -> Bool
$c/= :: Byte -> Byte -> Bool
== :: Byte -> Byte -> Bool
$c== :: Byte -> Byte -> Bool
Eq,Int -> Byte -> ShowS
[Byte] -> ShowS
Byte -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Byte] -> ShowS
$cshowList :: [Byte] -> ShowS
show :: Byte -> String
$cshow :: Byte -> String
showsPrec :: Int -> Byte -> ShowS
$cshowsPrec :: Int -> Byte -> ShowS
Show)
newtype NonNegativeInteger = NonNeg Integer deriving (NonNegativeInteger -> NonNegativeInteger -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NonNegativeInteger -> NonNegativeInteger -> Bool
$c/= :: NonNegativeInteger -> NonNegativeInteger -> Bool
== :: NonNegativeInteger -> NonNegativeInteger -> Bool
$c== :: NonNegativeInteger -> NonNegativeInteger -> Bool
Eq,Int -> NonNegativeInteger -> ShowS
[NonNegativeInteger] -> ShowS
NonNegativeInteger -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NonNegativeInteger] -> ShowS
$cshowList :: [NonNegativeInteger] -> ShowS
show :: NonNegativeInteger -> String
$cshow :: NonNegativeInteger -> String
showsPrec :: Int -> NonNegativeInteger -> ShowS
$cshowsPrec :: Int -> NonNegativeInteger -> ShowS
Show)
newtype UnsignedLong = ULong Word64 deriving (UnsignedLong -> UnsignedLong -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnsignedLong -> UnsignedLong -> Bool
$c/= :: UnsignedLong -> UnsignedLong -> Bool
== :: UnsignedLong -> UnsignedLong -> Bool
$c== :: UnsignedLong -> UnsignedLong -> Bool
Eq,Int -> UnsignedLong -> ShowS
[UnsignedLong] -> ShowS
UnsignedLong -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnsignedLong] -> ShowS
$cshowList :: [UnsignedLong] -> ShowS
show :: UnsignedLong -> String
$cshow :: UnsignedLong -> String
showsPrec :: Int -> UnsignedLong -> ShowS
$cshowsPrec :: Int -> UnsignedLong -> ShowS
Show)
newtype UnsignedInt = UInt Word32 deriving (UnsignedInt -> UnsignedInt -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnsignedInt -> UnsignedInt -> Bool
$c/= :: UnsignedInt -> UnsignedInt -> Bool
== :: UnsignedInt -> UnsignedInt -> Bool
$c== :: UnsignedInt -> UnsignedInt -> Bool
Eq,Int -> UnsignedInt -> ShowS
[UnsignedInt] -> ShowS
UnsignedInt -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnsignedInt] -> ShowS
$cshowList :: [UnsignedInt] -> ShowS
show :: UnsignedInt -> String
$cshow :: UnsignedInt -> String
showsPrec :: Int -> UnsignedInt -> ShowS
$cshowsPrec :: Int -> UnsignedInt -> ShowS
Show)
newtype UnsignedShort = UShort Word16 deriving (UnsignedShort -> UnsignedShort -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnsignedShort -> UnsignedShort -> Bool
$c/= :: UnsignedShort -> UnsignedShort -> Bool
== :: UnsignedShort -> UnsignedShort -> Bool
$c== :: UnsignedShort -> UnsignedShort -> Bool
Eq,Int -> UnsignedShort -> ShowS
[UnsignedShort] -> ShowS
UnsignedShort -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnsignedShort] -> ShowS
$cshowList :: [UnsignedShort] -> ShowS
show :: UnsignedShort -> String
$cshow :: UnsignedShort -> String
showsPrec :: Int -> UnsignedShort -> ShowS
$cshowsPrec :: Int -> UnsignedShort -> ShowS
Show)
newtype UnsignedByte = UByte Word8 deriving (UnsignedByte -> UnsignedByte -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnsignedByte -> UnsignedByte -> Bool
$c/= :: UnsignedByte -> UnsignedByte -> Bool
== :: UnsignedByte -> UnsignedByte -> Bool
$c== :: UnsignedByte -> UnsignedByte -> Bool
Eq,Int -> UnsignedByte -> ShowS
[UnsignedByte] -> ShowS
UnsignedByte -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnsignedByte] -> ShowS
$cshowList :: [UnsignedByte] -> ShowS
show :: UnsignedByte -> String
$cshow :: UnsignedByte -> String
showsPrec :: Int -> UnsignedByte -> ShowS
$cshowsPrec :: Int -> UnsignedByte -> ShowS
Show)
newtype PositiveInteger = Positive Integer deriving (PositiveInteger -> PositiveInteger -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PositiveInteger -> PositiveInteger -> Bool
$c/= :: PositiveInteger -> PositiveInteger -> Bool
== :: PositiveInteger -> PositiveInteger -> Bool
$c== :: PositiveInteger -> PositiveInteger -> Bool
Eq,Int -> PositiveInteger -> ShowS
[PositiveInteger] -> ShowS
PositiveInteger -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PositiveInteger] -> ShowS
$cshowList :: [PositiveInteger] -> ShowS
show :: PositiveInteger -> String
$cshow :: PositiveInteger -> String
showsPrec :: Int -> PositiveInteger -> ShowS
$cshowsPrec :: Int -> PositiveInteger -> ShowS
Show)
instance SimpleType Integer where
acceptingParser :: TextParser Integer
acceptingParser = forall a. Parse a => TextParser a
parse
simpleTypeText :: Integer -> String
simpleTypeText = forall a. Show a => a -> String
show
instance SimpleType NonPositiveInteger where
acceptingParser :: TextParser NonPositiveInteger
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> NonPositiveInteger
NonPos forall a. Parse a => TextParser a
parse
simpleTypeText :: NonPositiveInteger -> String
simpleTypeText (NonPos Integer
x) = forall a. Show a => a -> String
show Integer
x
instance SimpleType NegativeInteger where
acceptingParser :: TextParser NegativeInteger
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> NegativeInteger
Negative forall a. Parse a => TextParser a
parse
simpleTypeText :: NegativeInteger -> String
simpleTypeText (Negative Integer
x) = forall a. Show a => a -> String
show Integer
x
instance SimpleType Long where
acceptingParser :: TextParser Long
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int64 -> Long
Long forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger) forall a. Parse a => TextParser a
parse
simpleTypeText :: Long -> String
simpleTypeText (Long Int64
x) = forall a. Show a => a -> String
show Int64
x
instance SimpleType Int where
acceptingParser :: Parser Char Int
acceptingParser = forall a. Parse a => TextParser a
parse
simpleTypeText :: Int -> String
simpleTypeText = forall a. Show a => a -> String
show
instance SimpleType Short where
acceptingParser :: TextParser Short
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int16 -> Short
Short forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger) forall a. Parse a => TextParser a
parse
simpleTypeText :: Short -> String
simpleTypeText (Short Int16
x) = forall a. Show a => a -> String
show Int16
x
instance SimpleType Byte where
acceptingParser :: TextParser Byte
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int8 -> Byte
Byte forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger) forall a. Parse a => TextParser a
parse
simpleTypeText :: Byte -> String
simpleTypeText (Byte Int8
x) = forall a. Show a => a -> String
show Int8
x
instance SimpleType NonNegativeInteger where
acceptingParser :: TextParser NonNegativeInteger
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> NonNegativeInteger
NonNeg forall a. Parse a => TextParser a
parse
simpleTypeText :: NonNegativeInteger -> String
simpleTypeText (NonNeg Integer
x) = forall a. Show a => a -> String
show Integer
x
instance SimpleType UnsignedLong where
acceptingParser :: TextParser UnsignedLong
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Word64 -> UnsignedLong
ULong forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger) forall a. Parse a => TextParser a
parse
simpleTypeText :: UnsignedLong -> String
simpleTypeText (ULong Word64
x) = forall a. Show a => a -> String
show Word64
x
instance SimpleType UnsignedInt where
acceptingParser :: TextParser UnsignedInt
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Word32 -> UnsignedInt
UInt forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger) forall a. Parse a => TextParser a
parse
simpleTypeText :: UnsignedInt -> String
simpleTypeText (UInt Word32
x) = forall a. Show a => a -> String
show Word32
x
instance SimpleType UnsignedShort where
acceptingParser :: TextParser UnsignedShort
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Word16 -> UnsignedShort
UShort forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger) forall a. Parse a => TextParser a
parse
simpleTypeText :: UnsignedShort -> String
simpleTypeText (UShort Word16
x) = forall a. Show a => a -> String
show Word16
x
instance SimpleType UnsignedByte where
acceptingParser :: TextParser UnsignedByte
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Word8 -> UnsignedByte
UByte forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger) forall a. Parse a => TextParser a
parse
simpleTypeText :: UnsignedByte -> String
simpleTypeText (UByte Word8
x) = forall a. Show a => a -> String
show Word8
x
instance SimpleType PositiveInteger where
acceptingParser :: TextParser PositiveInteger
acceptingParser = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> PositiveInteger
Positive forall a. Parse a => TextParser a
parse
simpleTypeText :: PositiveInteger -> String
simpleTypeText (Positive Integer
x) = forall a. Show a => a -> String
show Integer
x