iri-0.4: RFC-based resource identifier library

Safe HaskellNone
LanguageHaskell2010

Iri.Data

Contents

Description

References:

Synopsis

Documentation

data Iri Source #

Thorough structure of IRI or URI.

Constructors

Iri !Scheme !Hierarchy !Query !Fragment 
Instances
Eq Iri Source # 
Instance details

Defined in Iri.Data.Instances.Eq

Methods

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

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

Ord Iri Source # 
Instance details

Defined in Iri.Data.Instances.Ord

Methods

compare :: Iri -> Iri -> Ordering #

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

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

(>) :: Iri -> Iri -> Bool #

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

max :: Iri -> Iri -> Iri #

min :: Iri -> Iri -> Iri #

Show Iri Source # 
Instance details

Defined in Iri.Data.Instances.Show

Methods

showsPrec :: Int -> Iri -> ShowS #

show :: Iri -> String #

showList :: [Iri] -> ShowS #

Generic Iri Source # 
Instance details

Defined in Iri.Data.Instances.Generic

Associated Types

type Rep Iri :: Type -> Type #

Methods

from :: Iri -> Rep Iri x #

to :: Rep Iri x -> Iri #

Lift Iri Source # 
Instance details

Defined in Iri.Data.Instances.Lift

Methods

lift :: Iri -> Q Exp #

Hashable Iri Source # 
Instance details

Defined in Iri.Data.Instances.Hashable

Methods

hashWithSalt :: Int -> Iri -> Int #

hash :: Iri -> Int #

type Rep Iri Source # 
Instance details

Defined in Iri.Data.Instances.Generic

newtype Scheme Source #

Constructors

Scheme ByteString 
Instances
Eq Scheme Source # 
Instance details

Defined in Iri.Data.Instances.Eq

Methods

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

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

Ord Scheme Source # 
Instance details

Defined in Iri.Data.Instances.Ord

Show Scheme Source # 
Instance details

Defined in Iri.Data.Instances.Show

Generic Scheme Source # 
Instance details

Defined in Iri.Data.Instances.Generic

Associated Types

type Rep Scheme :: Type -> Type #

Methods

from :: Scheme -> Rep Scheme x #

to :: Rep Scheme x -> Scheme #

Lift Scheme Source # 
Instance details

Defined in Iri.Data.Instances.Lift

Methods

lift :: Scheme -> Q Exp #

Hashable Scheme Source # 
Instance details

Defined in Iri.Data.Instances.Hashable

Methods

hashWithSalt :: Int -> Scheme -> Int #

hash :: Scheme -> Int #

type Rep Scheme Source # 
Instance details

Defined in Iri.Data.Instances.Generic

type Rep Scheme = D1 (MetaData "Scheme" "Iri.Data.Types" "iri-0.4-6utNI10Cmpx1Ay6lBJs6Kb" True) (C1 (MetaCons "Scheme" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

data Hierarchy Source #

Instances
Eq Hierarchy Source # 
Instance details

Defined in Iri.Data.Instances.Eq

Ord Hierarchy Source # 
Instance details

Defined in Iri.Data.Instances.Ord

Show Hierarchy Source # 
Instance details

Defined in Iri.Data.Instances.Show

Generic Hierarchy Source # 
Instance details

Defined in Iri.Data.Instances.Generic

Associated Types

type Rep Hierarchy :: Type -> Type #

Lift Hierarchy Source # 
Instance details

Defined in Iri.Data.Instances.Lift

Methods

lift :: Hierarchy -> Q Exp #

Hashable Hierarchy Source # 
Instance details

Defined in Iri.Data.Instances.Hashable

type Rep Hierarchy Source # 
Instance details

Defined in Iri.Data.Instances.Generic

data Authority Source #

Constructors

Authority !UserInfo !Host !Port 
Instances
Eq Authority Source # 
Instance details

Defined in Iri.Data.Instances.Eq

Ord Authority Source # 
Instance details

Defined in Iri.Data.Instances.Ord

Show Authority Source # 
Instance details

Defined in Iri.Data.Instances.Show

Generic Authority Source # 
Instance details

Defined in Iri.Data.Instances.Generic

Associated Types

type Rep Authority :: Type -> Type #

Lift Authority Source # 
Instance details

Defined in Iri.Data.Instances.Lift

Methods

lift :: Authority -> Q Exp #

Hashable Authority Source # 
Instance details

Defined in Iri.Data.Instances.Hashable

type Rep Authority Source # 
Instance details

Defined in Iri.Data.Instances.Generic

data UserInfo Source #

Instances
Eq UserInfo Source # 
Instance details

Defined in Iri.Data.Instances.Eq

Ord UserInfo Source # 
Instance details

Defined in Iri.Data.Instances.Ord

Show UserInfo Source # 
Instance details

Defined in Iri.Data.Instances.Show

Generic UserInfo Source # 
Instance details

Defined in Iri.Data.Instances.Generic

Associated Types

type Rep UserInfo :: Type -> Type #

Methods

from :: UserInfo -> Rep UserInfo x #

to :: Rep UserInfo x -> UserInfo #

Lift UserInfo Source # 
Instance details

Defined in Iri.Data.Instances.Lift

Methods

lift :: UserInfo -> Q Exp #

Hashable UserInfo Source # 
Instance details

Defined in Iri.Data.Instances.Hashable

Methods

hashWithSalt :: Int -> UserInfo -> Int #

hash :: UserInfo -> Int #

type Rep UserInfo Source # 
Instance details

Defined in Iri.Data.Instances.Generic

type Rep UserInfo = D1 (MetaData "UserInfo" "Iri.Data.Types" "iri-0.4-6utNI10Cmpx1Ay6lBJs6Kb" False) (C1 (MetaCons "PresentUserInfo" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 User) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Password)) :+: C1 (MetaCons "MissingUserInfo" PrefixI False) (U1 :: Type -> Type))

newtype User Source #

Constructors

User ByteString 
Instances
Eq User Source # 
Instance details

Defined in Iri.Data.Instances.Eq

Methods

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

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

Ord User Source # 
Instance details

Defined in Iri.Data.Instances.Ord

Methods

compare :: User -> User -> Ordering #

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

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

(>) :: User -> User -> Bool #

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

max :: User -> User -> User #

min :: User -> User -> User #

Show User Source # 
Instance details

Defined in Iri.Data.Instances.Show

Methods

showsPrec :: Int -> User -> ShowS #

show :: User -> String #

showList :: [User] -> ShowS #

Generic User Source # 
Instance details

Defined in Iri.Data.Instances.Generic

Associated Types

type Rep User :: Type -> Type #

Methods

from :: User -> Rep User x #

to :: Rep User x -> User #

Lift User Source # 
Instance details

Defined in Iri.Data.Instances.Lift

Methods

lift :: User -> Q Exp #

Hashable User Source # 
Instance details

Defined in Iri.Data.Instances.Hashable

Methods

hashWithSalt :: Int -> User -> Int #

hash :: User -> Int #

type Rep User Source # 
Instance details

Defined in Iri.Data.Instances.Generic

type Rep User = D1 (MetaData "User" "Iri.Data.Types" "iri-0.4-6utNI10Cmpx1Ay6lBJs6Kb" True) (C1 (MetaCons "User" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

data Password Source #

Instances
Eq Password Source # 
Instance details

Defined in Iri.Data.Instances.Eq

Ord Password Source # 
Instance details

Defined in Iri.Data.Instances.Ord

Show Password Source # 
Instance details

Defined in Iri.Data.Instances.Show

Generic Password Source # 
Instance details

Defined in Iri.Data.Instances.Generic

Associated Types

type Rep Password :: Type -> Type #

Methods

from :: Password -> Rep Password x #

to :: Rep Password x -> Password #

Lift Password Source # 
Instance details

Defined in Iri.Data.Instances.Lift

Methods

lift :: Password -> Q Exp #

Hashable Password Source # 
Instance details

Defined in Iri.Data.Instances.Hashable

Methods

hashWithSalt :: Int -> Password -> Int #

hash :: Password -> Int #

type Rep Password Source # 
Instance details

Defined in Iri.Data.Instances.Generic

type Rep Password = D1 (MetaData "Password" "Iri.Data.Types" "iri-0.4-6utNI10Cmpx1Ay6lBJs6Kb" False) (C1 (MetaCons "PresentPassword" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString)) :+: C1 (MetaCons "MissingPassword" PrefixI False) (U1 :: Type -> Type))

data Host Source #

Instances
Eq Host Source # 
Instance details

Defined in Iri.Data.Instances.Eq

Methods

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

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

Ord Host Source # 
Instance details

Defined in Iri.Data.Instances.Ord

Methods

compare :: Host -> Host -> Ordering #

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

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

(>) :: Host -> Host -> Bool #

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

max :: Host -> Host -> Host #

min :: Host -> Host -> Host #

Show Host Source # 
Instance details

Defined in Iri.Data.Instances.Show

Methods

showsPrec :: Int -> Host -> ShowS #

show :: Host -> String #

showList :: [Host] -> ShowS #

Generic Host Source # 
Instance details

Defined in Iri.Data.Instances.Generic

Associated Types

type Rep Host :: Type -> Type #

Methods

from :: Host -> Rep Host x #

to :: Rep Host x -> Host #

Lift Host Source # 
Instance details

Defined in Iri.Data.Instances.Lift

Methods

lift :: Host -> Q Exp #

Hashable Host Source # 
Instance details

Defined in Iri.Data.Instances.Hashable

Methods

hashWithSalt :: Int -> Host -> Int #

hash :: Host -> Int #

type Rep Host Source # 
Instance details

Defined in Iri.Data.Instances.Generic

newtype RegName Source #

Constructors

RegName (Vector DomainLabel) 
Instances
Eq RegName Source # 
Instance details

Defined in Iri.Data.Instances.Eq

Methods

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

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

Ord RegName Source # 
Instance details

Defined in Iri.Data.Instances.Ord

Show RegName Source # 
Instance details

Defined in Iri.Data.Instances.Show

Generic RegName Source # 
Instance details

Defined in Iri.Data.Instances.Generic

Associated Types

type Rep RegName :: Type -> Type #

Methods

from :: RegName -> Rep RegName x #

to :: Rep RegName x -> RegName #

Lift RegName Source # 
Instance details

Defined in Iri.Data.Instances.Lift

Methods

lift :: RegName -> Q Exp #

Hashable RegName Source # 
Instance details

Defined in Iri.Data.Instances.Hashable

Methods

hashWithSalt :: Int -> RegName -> Int #

hash :: RegName -> Int #

type Rep RegName Source # 
Instance details

Defined in Iri.Data.Instances.Generic

type Rep RegName = D1 (MetaData "RegName" "Iri.Data.Types" "iri-0.4-6utNI10Cmpx1Ay6lBJs6Kb" True) (C1 (MetaCons "RegName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector DomainLabel))))

data DomainLabel Source #

Constructors

DomainLabel Text 
Instances
Eq DomainLabel Source # 
Instance details

Defined in Iri.Data.Instances.Eq

Ord DomainLabel Source # 
Instance details

Defined in Iri.Data.Instances.Ord

Show DomainLabel Source # 
Instance details

Defined in Iri.Data.Instances.Show

Generic DomainLabel Source # 
Instance details

Defined in Iri.Data.Instances.Generic

Associated Types

type Rep DomainLabel :: Type -> Type #

Lift DomainLabel Source # 
Instance details

Defined in Iri.Data.Instances.Lift

Methods

lift :: DomainLabel -> Q Exp #

Hashable DomainLabel Source # 
Instance details

Defined in Iri.Data.Instances.Hashable

type Rep DomainLabel Source # 
Instance details

Defined in Iri.Data.Instances.Generic

type Rep DomainLabel = D1 (MetaData "DomainLabel" "Iri.Data.Types" "iri-0.4-6utNI10Cmpx1Ay6lBJs6Kb" False) (C1 (MetaCons "DomainLabel" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Port Source #

Instances
Eq Port Source # 
Instance details

Defined in Iri.Data.Instances.Eq

Methods

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

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

Ord Port Source # 
Instance details

Defined in Iri.Data.Instances.Ord

Methods

compare :: Port -> Port -> Ordering #

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

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

(>) :: Port -> Port -> Bool #

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

max :: Port -> Port -> Port #

min :: Port -> Port -> Port #

Show Port Source # 
Instance details

Defined in Iri.Data.Instances.Show

Methods

showsPrec :: Int -> Port -> ShowS #

show :: Port -> String #

showList :: [Port] -> ShowS #

Generic Port Source # 
Instance details

Defined in Iri.Data.Instances.Generic

Associated Types

type Rep Port :: Type -> Type #

Methods

from :: Port -> Rep Port x #

to :: Rep Port x -> Port #

Lift Port Source # 
Instance details

Defined in Iri.Data.Instances.Lift

Methods

lift :: Port -> Q Exp #

Hashable Port Source # 
Instance details

Defined in Iri.Data.Instances.Hashable

Methods

hashWithSalt :: Int -> Port -> Int #

hash :: Port -> Int #

type Rep Port Source # 
Instance details

Defined in Iri.Data.Instances.Generic

type Rep Port = D1 (MetaData "Port" "Iri.Data.Types" "iri-0.4-6utNI10Cmpx1Ay6lBJs6Kb" False) (C1 (MetaCons "PresentPort" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word16)) :+: C1 (MetaCons "MissingPort" PrefixI False) (U1 :: Type -> Type))

newtype Path Source #

Constructors

Path (Vector PathSegment) 
Instances
Eq Path Source # 
Instance details

Defined in Iri.Data.Instances.Eq

Methods

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

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

Ord Path Source # 
Instance details

Defined in Iri.Data.Instances.Ord

Methods

compare :: Path -> Path -> Ordering #

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

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

(>) :: Path -> Path -> Bool #

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

max :: Path -> Path -> Path #

min :: Path -> Path -> Path #

Show Path Source # 
Instance details

Defined in Iri.Data.Instances.Show

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

Generic Path Source # 
Instance details

Defined in Iri.Data.Instances.Generic

Associated Types

type Rep Path :: Type -> Type #

Methods

from :: Path -> Rep Path x #

to :: Rep Path x -> Path #

Lift Path Source # 
Instance details

Defined in Iri.Data.Instances.Lift

Methods

lift :: Path -> Q Exp #

Hashable Path Source # 
Instance details

Defined in Iri.Data.Instances.Hashable

Methods

hashWithSalt :: Int -> Path -> Int #

hash :: Path -> Int #

type Rep Path Source # 
Instance details

Defined in Iri.Data.Instances.Generic

type Rep Path = D1 (MetaData "Path" "Iri.Data.Types" "iri-0.4-6utNI10Cmpx1Ay6lBJs6Kb" True) (C1 (MetaCons "Path" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector PathSegment))))

newtype PathSegment Source #

Constructors

PathSegment ByteString 
Instances
Eq PathSegment Source # 
Instance details

Defined in Iri.Data.Instances.Eq

Ord PathSegment Source # 
Instance details

Defined in Iri.Data.Instances.Ord

Show PathSegment Source # 
Instance details

Defined in Iri.Data.Instances.Show

Generic PathSegment Source # 
Instance details

Defined in Iri.Data.Instances.Generic

Associated Types

type Rep PathSegment :: Type -> Type #

Lift PathSegment Source # 
Instance details

Defined in Iri.Data.Instances.Lift

Methods

lift :: PathSegment -> Q Exp #

Hashable PathSegment Source # 
Instance details

Defined in Iri.Data.Instances.Hashable

type Rep PathSegment Source # 
Instance details

Defined in Iri.Data.Instances.Generic

type Rep PathSegment = D1 (MetaData "PathSegment" "Iri.Data.Types" "iri-0.4-6utNI10Cmpx1Ay6lBJs6Kb" True) (C1 (MetaCons "PathSegment" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

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 percent-decoded bytes.

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

Constructors

Query ByteString 
Instances
Eq Query Source # 
Instance details

Defined in Iri.Data.Instances.Eq

Methods

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

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

Ord Query Source # 
Instance details

Defined in Iri.Data.Instances.Ord

Methods

compare :: Query -> Query -> Ordering #

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

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

(>) :: Query -> Query -> Bool #

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

max :: Query -> Query -> Query #

min :: Query -> Query -> Query #

Show Query Source # 
Instance details

Defined in Iri.Data.Instances.Show

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

Generic Query Source # 
Instance details

Defined in Iri.Data.Instances.Generic

Associated Types

type Rep Query :: Type -> Type #

Methods

from :: Query -> Rep Query x #

to :: Rep Query x -> Query #

Lift Query Source # 
Instance details

Defined in Iri.Data.Instances.Lift

Methods

lift :: Query -> Q Exp #

Hashable Query Source # 
Instance details

Defined in Iri.Data.Instances.Hashable

Methods

hashWithSalt :: Int -> Query -> Int #

hash :: Query -> Int #

type Rep Query Source # 
Instance details

Defined in Iri.Data.Instances.Generic

type Rep Query = D1 (MetaData "Query" "Iri.Data.Types" "iri-0.4-6utNI10Cmpx1Ay6lBJs6Kb" True) (C1 (MetaCons "Query" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

newtype Fragment Source #

Constructors

Fragment ByteString 
Instances
Eq Fragment Source # 
Instance details

Defined in Iri.Data.Instances.Eq

Ord Fragment Source # 
Instance details

Defined in Iri.Data.Instances.Ord

Show Fragment Source # 
Instance details

Defined in Iri.Data.Instances.Show

Generic Fragment Source # 
Instance details

Defined in Iri.Data.Instances.Generic

Associated Types

type Rep Fragment :: Type -> Type #

Methods

from :: Fragment -> Rep Fragment x #

to :: Rep Fragment x -> Fragment #

Lift Fragment Source # 
Instance details

Defined in Iri.Data.Instances.Lift

Methods

lift :: Fragment -> Q Exp #

Hashable Fragment Source # 
Instance details

Defined in Iri.Data.Instances.Hashable

Methods

hashWithSalt :: Int -> Fragment -> Int #

hash :: Fragment -> Int #

type Rep Fragment Source # 
Instance details

Defined in Iri.Data.Instances.Generic

type Rep Fragment = D1 (MetaData "Fragment" "Iri.Data.Types" "iri-0.4-6utNI10Cmpx1Ay6lBJs6Kb" True) (C1 (MetaCons "Fragment" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

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 URI 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
Instances
Eq HttpIri Source # 
Instance details

Defined in Iri.Data.Instances.Eq

Methods

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

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

Ord HttpIri Source # 
Instance details

Defined in Iri.Data.Instances.Ord

Show HttpIri Source # 
Instance details

Defined in Iri.Data.Instances.Show

Generic HttpIri Source # 
Instance details

Defined in Iri.Data.Instances.Generic

Associated Types

type Rep HttpIri :: Type -> Type #

Methods

from :: HttpIri -> Rep HttpIri x #

to :: Rep HttpIri x -> HttpIri #

Lift HttpIri Source # 
Instance details

Defined in Iri.Data.Instances.Lift

Methods

lift :: HttpIri -> Q Exp #

Hashable HttpIri Source # 
Instance details

Defined in Iri.Data.Instances.Hashable

Methods

hashWithSalt :: Int -> HttpIri -> Int #

hash :: HttpIri -> Int #

type Rep HttpIri Source # 
Instance details

Defined in Iri.Data.Instances.Generic

newtype Security Source #

Constructors

Security Bool 
Instances
Eq Security Source # 
Instance details

Defined in Iri.Data.Instances.Eq

Ord Security Source # 
Instance details

Defined in Iri.Data.Instances.Ord

Show Security Source # 
Instance details

Defined in Iri.Data.Instances.Show

Generic Security Source # 
Instance details

Defined in Iri.Data.Instances.Generic

Associated Types

type Rep Security :: Type -> Type #

Methods

from :: Security -> Rep Security x #

to :: Rep Security x -> Security #

Lift Security Source # 
Instance details

Defined in Iri.Data.Instances.Lift

Methods

lift :: Security -> Q Exp #

Hashable Security Source # 
Instance details

Defined in Iri.Data.Instances.Hashable

Methods

hashWithSalt :: Int -> Security -> Int #

hash :: Security -> Int #

type Rep Security Source # 
Instance details

Defined in Iri.Data.Instances.Generic

type Rep Security = D1 (MetaData "Security" "Iri.Data.Types" "iri-0.4-6utNI10Cmpx1Ay6lBJs6Kb" True) (C1 (MetaCons "Security" PrefixI False) (S1 (MetaSel (Nothing :: Maybe 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