iri-0.3.4: RFC-based International Resource Identifier library

Safe HaskellNone
LanguageHaskell2010

Iri.Data

Contents

Description

References:

Synopsis

Documentation

newtype Scheme Source #

Constructors

Scheme ByteString 

Instances

type Rep Scheme # 
type Rep Scheme = D1 * (MetaData "Scheme" "Iri.Data.Types" "iri-0.3.4-7LVCPccSqWN22kg3Nh0vxb" True) (C1 * (MetaCons "Scheme" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ByteString)))

data UserInfo Source #

Instances

type Rep UserInfo # 
type Rep UserInfo = D1 * (MetaData "UserInfo" "Iri.Data.Types" "iri-0.3.4-7LVCPccSqWN22kg3Nh0vxb" False) ((:+:) * (C1 * (MetaCons "PresentUserInfo" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * User)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Password)))) (C1 * (MetaCons "MissingUserInfo" PrefixI False) (U1 *)))

newtype User Source #

Constructors

User Text 

Instances

type Rep User # 
type Rep User = D1 * (MetaData "User" "Iri.Data.Types" "iri-0.3.4-7LVCPccSqWN22kg3Nh0vxb" True) (C1 * (MetaCons "User" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

data Password Source #

Instances

type Rep Password # 
type Rep Password = D1 * (MetaData "Password" "Iri.Data.Types" "iri-0.3.4-7LVCPccSqWN22kg3Nh0vxb" False) ((:+:) * (C1 * (MetaCons "PresentPassword" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) (C1 * (MetaCons "MissingPassword" PrefixI False) (U1 *)))

newtype RegName Source #

Constructors

RegName (Vector DomainLabel) 

Instances

type Rep RegName # 
type Rep RegName = D1 * (MetaData "RegName" "Iri.Data.Types" "iri-0.3.4-7LVCPccSqWN22kg3Nh0vxb" True) (C1 * (MetaCons "RegName" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Vector DomainLabel))))

newtype DomainLabel Source #

Constructors

DomainLabel Text 

Instances

type Rep DomainLabel # 
type Rep DomainLabel = D1 * (MetaData "DomainLabel" "Iri.Data.Types" "iri-0.3.4-7LVCPccSqWN22kg3Nh0vxb" True) (C1 * (MetaCons "DomainLabel" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

data Port Source #

Instances

type Rep Port # 
type Rep Port = D1 * (MetaData "Port" "Iri.Data.Types" "iri-0.3.4-7LVCPccSqWN22kg3Nh0vxb" False) ((:+:) * (C1 * (MetaCons "PresentPort" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word16))) (C1 * (MetaCons "MissingPort" PrefixI False) (U1 *)))

newtype Path Source #

Constructors

Path (Vector PathSegment) 

Instances

type Rep Path # 
type Rep Path = D1 * (MetaData "Path" "Iri.Data.Types" "iri-0.3.4-7LVCPccSqWN22kg3Nh0vxb" True) (C1 * (MetaCons "Path" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Vector PathSegment))))

newtype PathSegment Source #

Constructors

PathSegment Text 

Instances

type Rep PathSegment # 
type Rep PathSegment = D1 * (MetaData "PathSegment" "Iri.Data.Types" "iri-0.3.4-7LVCPccSqWN22kg3Nh0vxb" True) (C1 * (MetaCons "PathSegment" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

newtype Query Source #

Since the exact structure of the query string is not standardised and methods used to parse the query string may differ between websites, we simply represent it as a decoded Unicode string.

See https://en.wikipedia.org/wiki/Query_string.

Constructors

Query Text 

Instances

type Rep Query # 
type Rep Query = D1 * (MetaData "Query" "Iri.Data.Types" "iri-0.3.4-7LVCPccSqWN22kg3Nh0vxb" True) (C1 * (MetaCons "Query" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

newtype Fragment Source #

Constructors

Fragment Text 

Instances

type Rep Fragment # 
type Rep Fragment = D1 * (MetaData "Fragment" "Iri.Data.Types" "iri-0.3.4-7LVCPccSqWN22kg3Nh0vxb" True) (C1 * (MetaCons "Fragment" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

Special cases

HTTP special case

data HttpIri Source #

HTTP being by far the most common use-case for resource identifiers, it's been isolated into a dedicated data-type, which is optimised for that particular case.

Compared to the general IRI definition it:

  • only supports the HTTP and HTTPS schemes
  • misses the Username and Password components
  • requires the Host component
  • requires the Path component to be absolute

newtype Security Source #

Constructors

Security Bool 

Instances

type Rep Security # 
type Rep Security = D1 * (MetaData "Security" "Iri.Data.Types" "iri-0.3.4-7LVCPccSqWN22kg3Nh0vxb" True) (C1 * (MetaCons "Security" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))

httpIriFromIri :: Iri -> Either Text HttpIri Source #

Try to specialize a general IRI to HTTP

iriFromHttpIri :: HttpIri -> Iri Source #

Generalize an HTTP IRI to IRI