oasis-xrd-1.0: Extensible Resource Descriptor

Safe HaskellNone
LanguageHaskell2010

Data.XRD.Types

Contents

Synopsis

Documentation

Document fields

newtype Subject Source #

Constructors

Subject (URIRef Absolute) 

Instances

Eq Subject Source # 

Methods

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

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

Ord Subject Source # 
Show Subject Source # 
Generic Subject Source # 

Associated Types

type Rep Subject :: * -> * #

Methods

from :: Subject -> Rep Subject x #

to :: Rep Subject x -> Subject #

type Rep Subject Source # 
type Rep Subject = D1 * (MetaData "Subject" "Data.XRD.Types" "oasis-xrd-1.0-E5i91RPA6iP40fB0vtMXUY" True) (C1 * (MetaCons "Subject" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (URIRef Absolute))))

data Link Source #

newtype LinkType Source #

Constructors

LinkType Text 

Instances

data Title Source #

Constructors

Title (Maybe Text) Text 

Instances

Eq Title Source # 

Methods

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

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

Ord Title Source # 

Methods

compare :: Title -> Title -> Ordering #

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

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

(>) :: Title -> Title -> Bool #

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

max :: Title -> Title -> Title #

min :: Title -> Title -> Title #

Show Title Source # 

Methods

showsPrec :: Int -> Title -> ShowS #

show :: Title -> String #

showList :: [Title] -> ShowS #

Generic Title Source # 

Associated Types

type Rep Title :: * -> * #

Methods

from :: Title -> Rep Title x #

to :: Rep Title x -> Title #

type Rep Title Source # 

URI building helper

data URIParseError :: * #

Instances

Eq URIParseError 
Read URIParseError 
Show URIParseError 
Generic URIParseError 

Associated Types

type Rep URIParseError :: * -> * #

type Rep URIParseError 
type Rep URIParseError = D1 * (MetaData "URIParseError" "URI.ByteString.Types" "uri-bytestring-0.3.1.1-KSTApW5KrorDDU08vEXaTs" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "MalformedScheme" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * SchemaError))) (C1 * (MetaCons "MalformedUserInfo" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "MalformedQuery" PrefixI False) (U1 *)) (C1 * (MetaCons "MalformedFragment" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "MalformedHost" PrefixI False) (U1 *)) (C1 * (MetaCons "MalformedPort" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "MalformedPath" PrefixI False) (U1 *)) (C1 * (MetaCons "OtherError" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))))))