modern-uri-0.3.6.1: Modern library for working with URIs
Copyright© 2017–present Mark Karpov
LicenseBSD 3 clause
MaintainerMark Karpov <markkarpov92@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.URI

Description

This is a modern library for working with URIs as per RFC 3986:

https://tools.ietf.org/html/rfc3986

This module is intended to be imported qualified, e.g.:

import Text.URI (URI)
import qualified Text.URI as URI

See also Text.URI.Lens for lens, prisms, and traversals; see Text.URI.QQ for quasi-quoters for compile-time validation of URIs and refined text components.

Synopsis

Data types

data URI #

Uniform resource identifier (URI) reference. We use refined Text (RText l) here because information is presented in human-readable form, i.e. percent-decoded, and thus it may contain Unicode characters.

Constructors

URI 

Fields

Instances

Instances details
Arbitrary URI # 
Instance details

Defined in Text.URI.Types

Methods

arbitrary :: Gen URI #

shrink :: URI -> [URI] #

NFData URI # 
Instance details

Defined in Text.URI.Types

Methods

rnf :: URI -> () #

Data URI # 
Instance details

Defined in Text.URI.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> URI -> c URI #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c URI #

toConstr :: URI -> Constr #

dataTypeOf :: URI -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c URI) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c URI) #

gmapT :: (forall b. Data b => b -> b) -> URI -> URI #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> URI -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> URI -> r #

gmapQ :: (forall d. Data d => d -> u) -> URI -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> URI -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> URI -> m URI #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> URI -> m URI #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> URI -> m URI #

Generic URI # 
Instance details

Defined in Text.URI.Types

Associated Types

type Rep URI 
Instance details

Defined in Text.URI.Types

Methods

from :: URI -> Rep URI x #

to :: Rep URI x -> URI #

Show URI # 
Instance details

Defined in Text.URI.Types

Methods

showsPrec :: Int -> URI -> ShowS #

show :: URI -> String #

showList :: [URI] -> ShowS #

Eq URI # 
Instance details

Defined in Text.URI.Types

Methods

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

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

Ord URI # 
Instance details

Defined in Text.URI.Types

Methods

compare :: URI -> URI -> Ordering #

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

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

(>) :: URI -> URI -> Bool #

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

max :: URI -> URI -> URI #

min :: URI -> URI -> URI #

Hashable URI #

Since: 0.3.5.0

Instance details

Defined in Text.URI.Types

Methods

hashWithSalt :: Int -> URI -> Int #

hash :: URI -> Int #

Lift URI #

Since: 0.3.1.0

Instance details

Defined in Text.URI.Types

Methods

lift :: Quote m => URI -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => URI -> Code m URI #

type Rep URI # 
Instance details

Defined in Text.URI.Types

mkURI :: MonadThrow m => Text -> m URI #

Construct a URI from Text. The input you pass to mkURI must be a valid URI as per RFC 3986, that is, its components should be percent-encoded where necessary. In case of parse failure ParseException is thrown.

This function uses the parser parser under the hood, which you can also use directly in a Megaparsec parser.

mkURIBs :: MonadThrow m => ByteString -> m URI #

Construct a URI from ByteString. The input you pass to mkURIBs must be a valid URI as per RFC 3986, that is, its components should be percent-encoded where necessary. In case of parse failure ParseExceptionBs is thrown.

This function uses the parserBs parser under the hood, which you can also use directly in a Megaparsec parser.

Since: 0.3.3.0

emptyURI :: URI #

The empty URI.

Since: 0.2.1.0

makeAbsolute :: RText 'Scheme -> URI -> URI #

Make a given URI reference absolute using the supplied RText Scheme if necessary.

isPathAbsolute :: URI -> Bool #

Return True if path in a given URI is absolute.

Since: 0.1.0.0

relativeTo #

Arguments

:: URI

Reference URI to make absolute

-> URI

Base URI

-> Maybe URI

The target URI

relativeTo reference base makes the reference URI absolute resolving it against the base URI.

If the base URI is not absolute itself (that is, it has no scheme), this function returns Nothing.

See also: https://tools.ietf.org/html/rfc3986#section-5.2.

Since: 0.2.0.0

data Authority #

Authority component of URI.

Constructors

Authority 

Fields

Instances

Instances details
Arbitrary Authority # 
Instance details

Defined in Text.URI.Types

NFData Authority # 
Instance details

Defined in Text.URI.Types

Methods

rnf :: Authority -> () #

Data Authority # 
Instance details

Defined in Text.URI.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Authority -> c Authority #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Authority #

toConstr :: Authority -> Constr #

dataTypeOf :: Authority -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Authority) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Authority) #

gmapT :: (forall b. Data b => b -> b) -> Authority -> Authority #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Authority -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Authority -> r #

gmapQ :: (forall d. Data d => d -> u) -> Authority -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Authority -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Authority -> m Authority #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Authority -> m Authority #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Authority -> m Authority #

Generic Authority # 
Instance details

Defined in Text.URI.Types

Associated Types

type Rep Authority 
Instance details

Defined in Text.URI.Types

type Rep Authority = D1 ('MetaData "Authority" "Text.URI.Types" "modern-uri-0.3.6.1-L63vFQCGe5c96bTqxOmYcs" 'False) (C1 ('MetaCons "Authority" 'PrefixI 'True) (S1 ('MetaSel ('Just "authUserInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe UserInfo)) :*: (S1 ('MetaSel ('Just "authHost") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RText 'Host)) :*: S1 ('MetaSel ('Just "authPort") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Word)))))
Show Authority # 
Instance details

Defined in Text.URI.Types

Eq Authority # 
Instance details

Defined in Text.URI.Types

Ord Authority # 
Instance details

Defined in Text.URI.Types

Hashable Authority #

Since: 0.3.5.0

Instance details

Defined in Text.URI.Types

Lift Authority #

Since: 0.3.1.0

Instance details

Defined in Text.URI.Types

Methods

lift :: Quote m => Authority -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Authority -> Code m Authority #

type Rep Authority # 
Instance details

Defined in Text.URI.Types

type Rep Authority = D1 ('MetaData "Authority" "Text.URI.Types" "modern-uri-0.3.6.1-L63vFQCGe5c96bTqxOmYcs" 'False) (C1 ('MetaCons "Authority" 'PrefixI 'True) (S1 ('MetaSel ('Just "authUserInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe UserInfo)) :*: (S1 ('MetaSel ('Just "authHost") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RText 'Host)) :*: S1 ('MetaSel ('Just "authPort") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Word)))))

data UserInfo #

User info as a combination of username and password.

Constructors

UserInfo 

Fields

Instances

Instances details
Arbitrary UserInfo # 
Instance details

Defined in Text.URI.Types

NFData UserInfo # 
Instance details

Defined in Text.URI.Types

Methods

rnf :: UserInfo -> () #

Data UserInfo # 
Instance details

Defined in Text.URI.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UserInfo -> c UserInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UserInfo #

toConstr :: UserInfo -> Constr #

dataTypeOf :: UserInfo -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UserInfo) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserInfo) #

gmapT :: (forall b. Data b => b -> b) -> UserInfo -> UserInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserInfo -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> UserInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UserInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UserInfo -> m UserInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UserInfo -> m UserInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UserInfo -> m UserInfo #

Generic UserInfo # 
Instance details

Defined in Text.URI.Types

Associated Types

type Rep UserInfo 
Instance details

Defined in Text.URI.Types

type Rep UserInfo = D1 ('MetaData "UserInfo" "Text.URI.Types" "modern-uri-0.3.6.1-L63vFQCGe5c96bTqxOmYcs" 'False) (C1 ('MetaCons "UserInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "uiUsername") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RText 'Username)) :*: S1 ('MetaSel ('Just "uiPassword") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (RText 'Password)))))

Methods

from :: UserInfo -> Rep UserInfo x #

to :: Rep UserInfo x -> UserInfo #

Show UserInfo # 
Instance details

Defined in Text.URI.Types

Eq UserInfo # 
Instance details

Defined in Text.URI.Types

Ord UserInfo # 
Instance details

Defined in Text.URI.Types

Hashable UserInfo #

Since: 0.3.5.0

Instance details

Defined in Text.URI.Types

Methods

hashWithSalt :: Int -> UserInfo -> Int #

hash :: UserInfo -> Int #

Lift UserInfo #

Since: 0.3.1.0

Instance details

Defined in Text.URI.Types

Methods

lift :: Quote m => UserInfo -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => UserInfo -> Code m UserInfo #

type Rep UserInfo # 
Instance details

Defined in Text.URI.Types

type Rep UserInfo = D1 ('MetaData "UserInfo" "Text.URI.Types" "modern-uri-0.3.6.1-L63vFQCGe5c96bTqxOmYcs" 'False) (C1 ('MetaCons "UserInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "uiUsername") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RText 'Username)) :*: S1 ('MetaSel ('Just "uiPassword") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (RText 'Password)))))

data QueryParam #

Query parameter either in the form of flag or as a pair of key and value. A key cannot be empty, while a value can.

Constructors

QueryFlag (RText 'QueryKey)

Flag parameter

QueryParam (RText 'QueryKey) (RText 'QueryValue)

Key–value pair

Instances

Instances details
Arbitrary QueryParam # 
Instance details

Defined in Text.URI.Types

NFData QueryParam # 
Instance details

Defined in Text.URI.Types

Methods

rnf :: QueryParam -> () #

Data QueryParam # 
Instance details

Defined in Text.URI.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QueryParam -> c QueryParam #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QueryParam #

toConstr :: QueryParam -> Constr #

dataTypeOf :: QueryParam -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c QueryParam) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QueryParam) #

gmapT :: (forall b. Data b => b -> b) -> QueryParam -> QueryParam #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QueryParam -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QueryParam -> r #

gmapQ :: (forall d. Data d => d -> u) -> QueryParam -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> QueryParam -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> QueryParam -> m QueryParam #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QueryParam -> m QueryParam #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QueryParam -> m QueryParam #

Generic QueryParam # 
Instance details

Defined in Text.URI.Types

Associated Types

type Rep QueryParam 
Instance details

Defined in Text.URI.Types

Show QueryParam # 
Instance details

Defined in Text.URI.Types

Eq QueryParam # 
Instance details

Defined in Text.URI.Types

Ord QueryParam # 
Instance details

Defined in Text.URI.Types

Hashable QueryParam #

Since: 0.3.5.0

Instance details

Defined in Text.URI.Types

Lift QueryParam #

Since: 0.3.1.0

Instance details

Defined in Text.URI.Types

Methods

lift :: Quote m => QueryParam -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => QueryParam -> Code m QueryParam #

type Rep QueryParam # 
Instance details

Defined in Text.URI.Types

newtype ParseException #

Parse exception thrown by mkURI when a given Text value cannot be parsed as a URI.

Constructors

ParseException (ParseErrorBundle Text Void)

Arguments are: original input and parse error

Instances

Instances details
NFData ParseException # 
Instance details

Defined in Text.URI.Types

Methods

rnf :: ParseException -> () #

Data ParseException # 
Instance details

Defined in Text.URI.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParseException -> c ParseException #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ParseException #

toConstr :: ParseException -> Constr #

dataTypeOf :: ParseException -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ParseException) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ParseException) #

gmapT :: (forall b. Data b => b -> b) -> ParseException -> ParseException #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParseException -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParseException -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParseException -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParseException -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParseException -> m ParseException #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseException -> m ParseException #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseException -> m ParseException #

Exception ParseException # 
Instance details

Defined in Text.URI.Types

Generic ParseException # 
Instance details

Defined in Text.URI.Types

Associated Types

type Rep ParseException 
Instance details

Defined in Text.URI.Types

type Rep ParseException = D1 ('MetaData "ParseException" "Text.URI.Types" "modern-uri-0.3.6.1-L63vFQCGe5c96bTqxOmYcs" 'True) (C1 ('MetaCons "ParseException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ParseErrorBundle Text Void))))
Show ParseException # 
Instance details

Defined in Text.URI.Types

Eq ParseException # 
Instance details

Defined in Text.URI.Types

type Rep ParseException # 
Instance details

Defined in Text.URI.Types

type Rep ParseException = D1 ('MetaData "ParseException" "Text.URI.Types" "modern-uri-0.3.6.1-L63vFQCGe5c96bTqxOmYcs" 'True) (C1 ('MetaCons "ParseException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ParseErrorBundle Text Void))))

newtype ParseExceptionBs #

Parse exception thrown by mkURIBs when a given ByteString value cannot be parsed as a URI.

Since: 0.3.3.0

Constructors

ParseExceptionBs (ParseErrorBundle ByteString Void)

Arguments are: original input and parse error

Instances

Instances details
NFData ParseExceptionBs # 
Instance details

Defined in Text.URI.Types

Methods

rnf :: ParseExceptionBs -> () #

Data ParseExceptionBs # 
Instance details

Defined in Text.URI.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParseExceptionBs -> c ParseExceptionBs #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ParseExceptionBs #

toConstr :: ParseExceptionBs -> Constr #

dataTypeOf :: ParseExceptionBs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ParseExceptionBs) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ParseExceptionBs) #

gmapT :: (forall b. Data b => b -> b) -> ParseExceptionBs -> ParseExceptionBs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParseExceptionBs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParseExceptionBs -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParseExceptionBs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParseExceptionBs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParseExceptionBs -> m ParseExceptionBs #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseExceptionBs -> m ParseExceptionBs #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseExceptionBs -> m ParseExceptionBs #

Exception ParseExceptionBs # 
Instance details

Defined in Text.URI.Types

Generic ParseExceptionBs # 
Instance details

Defined in Text.URI.Types

Associated Types

type Rep ParseExceptionBs 
Instance details

Defined in Text.URI.Types

type Rep ParseExceptionBs = D1 ('MetaData "ParseExceptionBs" "Text.URI.Types" "modern-uri-0.3.6.1-L63vFQCGe5c96bTqxOmYcs" 'True) (C1 ('MetaCons "ParseExceptionBs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ParseErrorBundle ByteString Void))))
Show ParseExceptionBs # 
Instance details

Defined in Text.URI.Types

Eq ParseExceptionBs # 
Instance details

Defined in Text.URI.Types

type Rep ParseExceptionBs # 
Instance details

Defined in Text.URI.Types

type Rep ParseExceptionBs = D1 ('MetaData "ParseExceptionBs" "Text.URI.Types" "modern-uri-0.3.6.1-L63vFQCGe5c96bTqxOmYcs" 'True) (C1 ('MetaCons "ParseExceptionBs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ParseErrorBundle ByteString Void))))

Refined text

Refined text values can only be created by using the smart constructors listed below, such as mkScheme. This eliminates the possibility of having an invalid component in URI which could invalidate the whole URI.

Note that the refined text RText type is labelled at the type level with RTextLabels, which see.

When an invalid Text value is passed to a smart constructor, it rejects it by throwing the RTextException. Remember that the Maybe datatype is also an instance of MonadThrow, and so one could as well use the smart constructors in the Maybe monad.

data RText (l :: RTextLabel) #

Refined text labelled at the type level.

Instances

Instances details
Typeable l => Lift (RText l :: Type) #

Since: 0.3.1.0

Instance details

Defined in Text.URI.Types

Methods

lift :: Quote m => RText l -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => RText l -> Code m (RText l) #

Arbitrary (RText 'Fragment) # 
Instance details

Defined in Text.URI.Types

Arbitrary (RText 'Host) # 
Instance details

Defined in Text.URI.Types

Methods

arbitrary :: Gen (RText 'Host) #

shrink :: RText 'Host -> [RText 'Host] #

Arbitrary (RText 'Password) # 
Instance details

Defined in Text.URI.Types

Arbitrary (RText 'PathPiece) # 
Instance details

Defined in Text.URI.Types

Arbitrary (RText 'QueryKey) # 
Instance details

Defined in Text.URI.Types

Arbitrary (RText 'QueryValue) # 
Instance details

Defined in Text.URI.Types

Arbitrary (RText 'Scheme) # 
Instance details

Defined in Text.URI.Types

Arbitrary (RText 'Username) # 
Instance details

Defined in Text.URI.Types

NFData (RText l) # 
Instance details

Defined in Text.URI.Types

Methods

rnf :: RText l -> () #

Typeable l => Data (RText l) # 
Instance details

Defined in Text.URI.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RText l -> c (RText l) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RText l) #

toConstr :: RText l -> Constr #

dataTypeOf :: RText l -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RText l)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RText l)) #

gmapT :: (forall b. Data b => b -> b) -> RText l -> RText l #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RText l -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RText l -> r #

gmapQ :: (forall d. Data d => d -> u) -> RText l -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RText l -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RText l -> m (RText l) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RText l -> m (RText l) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RText l -> m (RText l) #

Generic (RText l) # 
Instance details

Defined in Text.URI.Types

Associated Types

type Rep (RText l) 
Instance details

Defined in Text.URI.Types

type Rep (RText l) = D1 ('MetaData "RText" "Text.URI.Types" "modern-uri-0.3.6.1-L63vFQCGe5c96bTqxOmYcs" 'True) (C1 ('MetaCons "RText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

Methods

from :: RText l -> Rep (RText l) x #

to :: Rep (RText l) x -> RText l #

Show (RText l) # 
Instance details

Defined in Text.URI.Types

Methods

showsPrec :: Int -> RText l -> ShowS #

show :: RText l -> String #

showList :: [RText l] -> ShowS #

Eq (RText l) # 
Instance details

Defined in Text.URI.Types

Methods

(==) :: RText l -> RText l -> Bool #

(/=) :: RText l -> RText l -> Bool #

Ord (RText l) # 
Instance details

Defined in Text.URI.Types

Methods

compare :: RText l -> RText l -> Ordering #

(<) :: RText l -> RText l -> Bool #

(<=) :: RText l -> RText l -> Bool #

(>) :: RText l -> RText l -> Bool #

(>=) :: RText l -> RText l -> Bool #

max :: RText l -> RText l -> RText l #

min :: RText l -> RText l -> RText l #

Hashable (RText l) #

Since: 0.3.5.0

Instance details

Defined in Text.URI.Types

Methods

hashWithSalt :: Int -> RText l -> Int #

hash :: RText l -> Int #

type Rep (RText l) # 
Instance details

Defined in Text.URI.Types

type Rep (RText l) = D1 ('MetaData "RText" "Text.URI.Types" "modern-uri-0.3.6.1-L63vFQCGe5c96bTqxOmYcs" 'True) (C1 ('MetaCons "RText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data RTextLabel #

Refined text labels.

Instances

Instances details
Data RTextLabel # 
Instance details

Defined in Text.URI.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RTextLabel -> c RTextLabel #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RTextLabel #

toConstr :: RTextLabel -> Constr #

dataTypeOf :: RTextLabel -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RTextLabel) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RTextLabel) #

gmapT :: (forall b. Data b => b -> b) -> RTextLabel -> RTextLabel #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RTextLabel -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RTextLabel -> r #

gmapQ :: (forall d. Data d => d -> u) -> RTextLabel -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RTextLabel -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RTextLabel -> m RTextLabel #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RTextLabel -> m RTextLabel #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RTextLabel -> m RTextLabel #

Generic RTextLabel # 
Instance details

Defined in Text.URI.Types

Associated Types

type Rep RTextLabel 
Instance details

Defined in Text.URI.Types

type Rep RTextLabel = D1 ('MetaData "RTextLabel" "Text.URI.Types" "modern-uri-0.3.6.1-L63vFQCGe5c96bTqxOmYcs" 'False) (((C1 ('MetaCons "Scheme" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Host" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Username" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Password" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PathPiece" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QueryKey" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "QueryValue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Fragment" 'PrefixI 'False) (U1 :: Type -> Type))))
Show RTextLabel # 
Instance details

Defined in Text.URI.Types

Eq RTextLabel # 
Instance details

Defined in Text.URI.Types

Ord RTextLabel # 
Instance details

Defined in Text.URI.Types

type Rep RTextLabel # 
Instance details

Defined in Text.URI.Types

type Rep RTextLabel = D1 ('MetaData "RTextLabel" "Text.URI.Types" "modern-uri-0.3.6.1-L63vFQCGe5c96bTqxOmYcs" 'False) (((C1 ('MetaCons "Scheme" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Host" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Username" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Password" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PathPiece" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QueryKey" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "QueryValue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Fragment" 'PrefixI 'False) (U1 :: Type -> Type))))

mkScheme :: MonadThrow m => Text -> m (RText 'Scheme) #

Lift a Text value into RText Scheme.

Scheme names consist of a sequence of characters beginning with a letter and followed by any combination of letters, digits, plus "+", period ".", or hyphen "-".

This smart constructor performs normalization of valid schemes by converting them to lower case.

See also: https://tools.ietf.org/html/rfc3986#section-3.1

mkHost :: MonadThrow m => Text -> m (RText 'Host) #

Lift a Text value into RText Host.

The host sub-component of authority is identified by an IP literal encapsulated within square brackets, an IPv4 address in dotted-decimal form, or a registered name.

This smart constructor performs normalization of valid hosts by converting them to lower case.

See also: https://tools.ietf.org/html/rfc3986#section-3.2.2

mkUsername :: MonadThrow m => Text -> m (RText 'Username) #

Lift a Text value into RText Username.

This smart constructor does not perform any sort of normalization.

See also: https://tools.ietf.org/html/rfc3986#section-3.2.1

mkPassword :: MonadThrow m => Text -> m (RText 'Password) #

Lift a Text value into RText Password.

This smart constructor does not perform any sort of normalization.

See also: https://tools.ietf.org/html/rfc3986#section-3.2.1

mkPathPiece :: MonadThrow m => Text -> m (RText 'PathPiece) #

Lift a Text value into RText PathPiece.

This smart constructor does not perform any sort of normalization.

See also: https://tools.ietf.org/html/rfc3986#section-3.3

mkQueryKey :: MonadThrow m => Text -> m (RText 'QueryKey) #

Lift a Text value into 'RText QueryKey.

This smart constructor does not perform any sort of normalization.

See also: https://tools.ietf.org/html/rfc3986#section-3.4

mkQueryValue :: MonadThrow m => Text -> m (RText 'QueryValue) #

Lift a Text value into RText QueryValue.

This smart constructor does not perform any sort of normalization.

See also: https://tools.ietf.org/html/rfc3986#section-3.4

mkFragment :: MonadThrow m => Text -> m (RText 'Fragment) #

Lift a Text value into RText Fragment.

This smart constructor does not perform any sort of normalization.

See also: https://tools.ietf.org/html/rfc3986#section-3.5

unRText :: forall (l :: RTextLabel). RText l -> Text #

Project a plain strict Text value from a refined RText l value.

data RTextException #

The exception is thrown when a refined RText l value cannot be constructed due to the fact that given Text value is not correct.

Constructors

RTextException RTextLabel Text

RTextLabel identifying what sort of refined text value could not be constructed and the input that was supplied, as a Text value

Instances

Instances details
Data RTextException # 
Instance details

Defined in Text.URI.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RTextException -> c RTextException #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RTextException #

toConstr :: RTextException -> Constr #

dataTypeOf :: RTextException -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RTextException) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RTextException) #

gmapT :: (forall b. Data b => b -> b) -> RTextException -> RTextException #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RTextException -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RTextException -> r #

gmapQ :: (forall d. Data d => d -> u) -> RTextException -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RTextException -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RTextException -> m RTextException #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RTextException -> m RTextException #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RTextException -> m RTextException #

Exception RTextException # 
Instance details

Defined in Text.URI.Types

Generic RTextException # 
Instance details

Defined in Text.URI.Types

Associated Types

type Rep RTextException 
Instance details

Defined in Text.URI.Types

type Rep RTextException = D1 ('MetaData "RTextException" "Text.URI.Types" "modern-uri-0.3.6.1-L63vFQCGe5c96bTqxOmYcs" 'False) (C1 ('MetaCons "RTextException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RTextLabel) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))
Show RTextException # 
Instance details

Defined in Text.URI.Types

Eq RTextException # 
Instance details

Defined in Text.URI.Types

Ord RTextException # 
Instance details

Defined in Text.URI.Types

type Rep RTextException # 
Instance details

Defined in Text.URI.Types

type Rep RTextException = D1 ('MetaData "RTextException" "Text.URI.Types" "modern-uri-0.3.6.1-L63vFQCGe5c96bTqxOmYcs" 'False) (C1 ('MetaCons "RTextException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RTextLabel) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

Parsing

The input you feed into the parsers must be a valid URI as per RFC 3986, that is, its components should be percent-encoded where necessary.

parser :: MonadParsec e Text m => m URI #

This parser can be used to parse URI from strict Text. Remember to use a concrete non-polymorphic parser type for efficiency.

parserBs :: MonadParsec e ByteString m => m URI #

This parser can be used to parse URI from strict ByteString. Remember to use a concrete non-polymorphic parser type for efficiency.

Since: 0.0.2.0

Rendering

Rendering functions take care of constructing correct URI representation as per RFC 3986, that is, percent-encoding will be applied when necessary automatically.

render :: URI -> Text #

Render a given URI value as strict Text.

render' :: URI -> Builder #

Render a given URI value as a Builder.

renderBs :: URI -> ByteString #

Render a given URI value as a strict ByteString.

renderBs' :: URI -> Builder #

Render a given URI value as a Builder.

renderStr :: URI -> String #

Render a given URI value as a String.

Since: 0.0.2.0

renderStr' :: URI -> ShowS #

Render a given URI value as ShowS.

Since: 0.0.2.0