hydra-0.1.1: Type-aware transformations for data and programs
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hydra.Ext.Xml.Schema

Description

A partial XML Schema model, focusing on datatypes. All simple datatypes (i.e. xsd:anySimpleType and below) are included. | See: https://www.w3.org/TR/xmlschema-2 | Note: for most of the XML Schema datatype definitions included here, the associated Hydra type is simply | the string type. Exceptions are made for xsd:boolean and most of the numeric types, where there is a clearly | corresponding Hydra literal type.

Synopsis

Documentation

newtype AnyType Source #

Constructors

AnyType 

Fields

Instances

Instances details
Read AnyType Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show AnyType Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Eq AnyType Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: AnyType -> AnyType -> Bool #

(/=) :: AnyType -> AnyType -> Bool #

Ord AnyType Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

newtype AnyURI Source #

Constructors

AnyURI 

Fields

Instances

Instances details
Read AnyURI Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show AnyURI Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Eq AnyURI Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: AnyURI -> AnyURI -> Bool #

(/=) :: AnyURI -> AnyURI -> Bool #

Ord AnyURI Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

newtype Boolean Source #

Constructors

Boolean 

Fields

Instances

Instances details
Read Boolean Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show Boolean Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Eq Boolean Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: Boolean -> Boolean -> Bool #

(/=) :: Boolean -> Boolean -> Bool #

Ord Boolean Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

newtype Byte Source #

Constructors

Byte 

Fields

Instances

Instances details
Read Byte Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show Byte Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

showsPrec :: Int -> Byte -> ShowS #

show :: Byte -> String #

showList :: [Byte] -> ShowS #

Eq Byte Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: Byte -> Byte -> Bool #

(/=) :: Byte -> Byte -> Bool #

Ord Byte Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

compare :: Byte -> Byte -> Ordering #

(<) :: Byte -> Byte -> Bool #

(<=) :: Byte -> Byte -> Bool #

(>) :: Byte -> Byte -> Bool #

(>=) :: Byte -> Byte -> Bool #

max :: Byte -> Byte -> Byte #

min :: Byte -> Byte -> Byte #

newtype Date Source #

Constructors

Date 

Fields

Instances

Instances details
Read Date Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show Date Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

showsPrec :: Int -> Date -> ShowS #

show :: Date -> String #

showList :: [Date] -> ShowS #

Eq Date Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: Date -> Date -> Bool #

(/=) :: Date -> Date -> Bool #

Ord Date Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

compare :: Date -> Date -> Ordering #

(<) :: Date -> Date -> Bool #

(<=) :: Date -> Date -> Bool #

(>) :: Date -> Date -> Bool #

(>=) :: Date -> Date -> Bool #

max :: Date -> Date -> Date #

min :: Date -> Date -> Date #

newtype DateTime Source #

Constructors

DateTime 

Fields

Instances

Instances details
Read DateTime Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show DateTime Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Eq DateTime Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Ord DateTime Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

newtype Decimal Source #

Constructors

Decimal 

Fields

Instances

Instances details
Read Decimal Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show Decimal Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Eq Decimal Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: Decimal -> Decimal -> Bool #

(/=) :: Decimal -> Decimal -> Bool #

Ord Decimal Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

newtype Double_ Source #

Constructors

Double_ 

Fields

Instances

Instances details
Read Double_ Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show Double_ Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Eq Double_ Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: Double_ -> Double_ -> Bool #

(/=) :: Double_ -> Double_ -> Bool #

Ord Double_ Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

newtype Duration Source #

Constructors

Duration 

Fields

Instances

Instances details
Read Duration Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show Duration Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Eq Duration Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Ord Duration Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

newtype ENTITIES Source #

Constructors

ENTITIES 

Fields

Instances

Instances details
Read ENTITIES Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show ENTITIES Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Eq ENTITIES Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Ord ENTITIES Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

newtype ENTITY Source #

Constructors

ENTITY 

Fields

Instances

Instances details
Read ENTITY Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show ENTITY Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Eq ENTITY Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: ENTITY -> ENTITY -> Bool #

(/=) :: ENTITY -> ENTITY -> Bool #

Ord ENTITY Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

newtype Float_ Source #

Constructors

Float_ 

Fields

Instances

Instances details
Read Float_ Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show Float_ Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Eq Float_ Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: Float_ -> Float_ -> Bool #

(/=) :: Float_ -> Float_ -> Bool #

Ord Float_ Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

newtype GDay Source #

Constructors

GDay 

Fields

Instances

Instances details
Read GDay Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show GDay Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

showsPrec :: Int -> GDay -> ShowS #

show :: GDay -> String #

showList :: [GDay] -> ShowS #

Eq GDay Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: GDay -> GDay -> Bool #

(/=) :: GDay -> GDay -> Bool #

Ord GDay Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

compare :: GDay -> GDay -> Ordering #

(<) :: GDay -> GDay -> Bool #

(<=) :: GDay -> GDay -> Bool #

(>) :: GDay -> GDay -> Bool #

(>=) :: GDay -> GDay -> Bool #

max :: GDay -> GDay -> GDay #

min :: GDay -> GDay -> GDay #

newtype GMonth Source #

Constructors

GMonth 

Fields

Instances

Instances details
Read GMonth Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show GMonth Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Eq GMonth Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: GMonth -> GMonth -> Bool #

(/=) :: GMonth -> GMonth -> Bool #

Ord GMonth Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

newtype GYear Source #

Constructors

GYear 

Fields

Instances

Instances details
Read GYear Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show GYear Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

showsPrec :: Int -> GYear -> ShowS #

show :: GYear -> String #

showList :: [GYear] -> ShowS #

Eq GYear Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: GYear -> GYear -> Bool #

(/=) :: GYear -> GYear -> Bool #

Ord GYear Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

compare :: GYear -> GYear -> Ordering #

(<) :: GYear -> GYear -> Bool #

(<=) :: GYear -> GYear -> Bool #

(>) :: GYear -> GYear -> Bool #

(>=) :: GYear -> GYear -> Bool #

max :: GYear -> GYear -> GYear #

min :: GYear -> GYear -> GYear #

newtype ID Source #

Constructors

ID 

Fields

Instances

Instances details
Read ID Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show ID Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

showsPrec :: Int -> ID -> ShowS #

show :: ID -> String #

showList :: [ID] -> ShowS #

Eq ID Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: ID -> ID -> Bool #

(/=) :: ID -> ID -> Bool #

Ord ID Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

compare :: ID -> ID -> Ordering #

(<) :: ID -> ID -> Bool #

(<=) :: ID -> ID -> Bool #

(>) :: ID -> ID -> Bool #

(>=) :: ID -> ID -> Bool #

max :: ID -> ID -> ID #

min :: ID -> ID -> ID #

newtype IDREF Source #

Constructors

IDREF 

Fields

Instances

Instances details
Read IDREF Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show IDREF Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

showsPrec :: Int -> IDREF -> ShowS #

show :: IDREF -> String #

showList :: [IDREF] -> ShowS #

Eq IDREF Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: IDREF -> IDREF -> Bool #

(/=) :: IDREF -> IDREF -> Bool #

Ord IDREF Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

compare :: IDREF -> IDREF -> Ordering #

(<) :: IDREF -> IDREF -> Bool #

(<=) :: IDREF -> IDREF -> Bool #

(>) :: IDREF -> IDREF -> Bool #

(>=) :: IDREF -> IDREF -> Bool #

max :: IDREF -> IDREF -> IDREF #

min :: IDREF -> IDREF -> IDREF #

newtype IDREFS Source #

Constructors

IDREFS 

Fields

Instances

Instances details
Read IDREFS Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show IDREFS Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Eq IDREFS Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: IDREFS -> IDREFS -> Bool #

(/=) :: IDREFS -> IDREFS -> Bool #

Ord IDREFS Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

newtype Int_ Source #

Constructors

Int_ 

Fields

Instances

Instances details
Read Int_ Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show Int_ Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

showsPrec :: Int -> Int_ -> ShowS #

show :: Int_ -> String #

showList :: [Int_] -> ShowS #

Eq Int_ Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: Int_ -> Int_ -> Bool #

(/=) :: Int_ -> Int_ -> Bool #

Ord Int_ Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

compare :: Int_ -> Int_ -> Ordering #

(<) :: Int_ -> Int_ -> Bool #

(<=) :: Int_ -> Int_ -> Bool #

(>) :: Int_ -> Int_ -> Bool #

(>=) :: Int_ -> Int_ -> Bool #

max :: Int_ -> Int_ -> Int_ #

min :: Int_ -> Int_ -> Int_ #

newtype Integer_ Source #

Constructors

Integer_ 

Fields

Instances

Instances details
Read Integer_ Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show Integer_ Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Eq Integer_ Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Ord Integer_ Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

newtype Language Source #

Constructors

Language 

Fields

Instances

Instances details
Read Language Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show Language Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Eq Language Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Ord Language Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

newtype Long Source #

Constructors

Long 

Fields

Instances

Instances details
Read Long Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show Long Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

showsPrec :: Int -> Long -> ShowS #

show :: Long -> String #

showList :: [Long] -> ShowS #

Eq Long Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: Long -> Long -> Bool #

(/=) :: Long -> Long -> Bool #

Ord Long Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

compare :: Long -> Long -> Ordering #

(<) :: Long -> Long -> Bool #

(<=) :: Long -> Long -> Bool #

(>) :: Long -> Long -> Bool #

(>=) :: Long -> Long -> Bool #

max :: Long -> Long -> Long #

min :: Long -> Long -> Long #

newtype NMTOKEN Source #

Constructors

NMTOKEN 

Fields

Instances

Instances details
Read NMTOKEN Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show NMTOKEN Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Eq NMTOKEN Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: NMTOKEN -> NMTOKEN -> Bool #

(/=) :: NMTOKEN -> NMTOKEN -> Bool #

Ord NMTOKEN Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

newtype NOTATION Source #

Constructors

NOTATION 

Fields

Instances

Instances details
Read NOTATION Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show NOTATION Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Eq NOTATION Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Ord NOTATION Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

newtype Name Source #

Constructors

Name 

Fields

Instances

Instances details
Read Name Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show Name Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Eq Name Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Ord Name Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

newtype QName Source #

Constructors

QName 

Fields

Instances

Instances details
Read QName Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show QName Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

showsPrec :: Int -> QName -> ShowS #

show :: QName -> String #

showList :: [QName] -> ShowS #

Eq QName Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: QName -> QName -> Bool #

(/=) :: QName -> QName -> Bool #

Ord QName Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

compare :: QName -> QName -> Ordering #

(<) :: QName -> QName -> Bool #

(<=) :: QName -> QName -> Bool #

(>) :: QName -> QName -> Bool #

(>=) :: QName -> QName -> Bool #

max :: QName -> QName -> QName #

min :: QName -> QName -> QName #

newtype Short Source #

Constructors

Short 

Fields

Instances

Instances details
Read Short Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show Short Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

showsPrec :: Int -> Short -> ShowS #

show :: Short -> String #

showList :: [Short] -> ShowS #

Eq Short Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: Short -> Short -> Bool #

(/=) :: Short -> Short -> Bool #

Ord Short Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

compare :: Short -> Short -> Ordering #

(<) :: Short -> Short -> Bool #

(<=) :: Short -> Short -> Bool #

(>) :: Short -> Short -> Bool #

(>=) :: Short -> Short -> Bool #

max :: Short -> Short -> Short #

min :: Short -> Short -> Short #

newtype String_ Source #

Constructors

String_ 

Fields

Instances

Instances details
Read String_ Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show String_ Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Eq String_ Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: String_ -> String_ -> Bool #

(/=) :: String_ -> String_ -> Bool #

Ord String_ Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

newtype Time Source #

Constructors

Time 

Fields

Instances

Instances details
Read Time Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show Time Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

Eq Time Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: Time -> Time -> Bool #

(/=) :: Time -> Time -> Bool #

Ord Time Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

compare :: Time -> Time -> Ordering #

(<) :: Time -> Time -> Bool #

(<=) :: Time -> Time -> Bool #

(>) :: Time -> Time -> Bool #

(>=) :: Time -> Time -> Bool #

max :: Time -> Time -> Time #

min :: Time -> Time -> Time #

newtype Token Source #

Constructors

Token 

Fields

Instances

Instances details
Read Token Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show Token Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Eq Token Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

(==) :: Token -> Token -> Bool #

(/=) :: Token -> Token -> Bool #

Ord Token Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Methods

compare :: Token -> Token -> Ordering #

(<) :: Token -> Token -> Bool #

(<=) :: Token -> Token -> Bool #

(>) :: Token -> Token -> Bool #

(>=) :: Token -> Token -> Bool #

max :: Token -> Token -> Token #

min :: Token -> Token -> Token #

data Datatype Source #

Instances

Instances details
Read Datatype Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Show Datatype Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Eq Datatype Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema

Ord Datatype Source # 
Instance details

Defined in Hydra.Ext.Xml.Schema