modern-uri-0.3.1.0: Modern library for working with URIs

Copyright© 2017–present Mark Karpov
LicenseBSD 3 clause
MaintainerMark Karpov <markkarpov92@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.URI

Contents

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 Source #

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

Defined in Text.URI.Types

Methods

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

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

Data URI Source # 
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 :: (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

Ord URI Source # 
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

Show URI Source # 
Instance details

Defined in Text.URI.Types

Methods

showsPrec :: Int -> URI -> ShowS

show :: URI -> String

showList :: [URI] -> ShowS

Generic URI Source # 
Instance details

Defined in Text.URI.Types

Associated Types

type Rep URI :: Type -> Type

Methods

from :: URI -> Rep URI x

to :: Rep URI x -> URI

Lift URI Source #

Since: 0.3.1.0

Instance details

Defined in Text.URI.Types

Methods

lift :: URI -> Q Exp

NFData URI Source # 
Instance details

Defined in Text.URI.Types

Methods

rnf :: URI -> ()

Arbitrary URI Source # 
Instance details

Defined in Text.URI.Types

Methods

arbitrary :: Gen URI

shrink :: URI -> [URI]

type Rep URI Source # 
Instance details

Defined in Text.URI.Types

type Rep URI = D1 (MetaData "URI" "Text.URI.Types" "modern-uri-0.3.1.0-8gVJU0yyGqqBmSEM0pAZya" False) (C1 (MetaCons "URI" PrefixI True) ((S1 (MetaSel (Just "uriScheme") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (RText Scheme))) :*: S1 (MetaSel (Just "uriAuthority") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either Bool Authority))) :*: (S1 (MetaSel (Just "uriPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Bool, NonEmpty (RText PathPiece)))) :*: (S1 (MetaSel (Just "uriQuery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [QueryParam]) :*: S1 (MetaSel (Just "uriFragment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (RText Fragment)))))))

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

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.

emptyURI :: URI Source #

The empty URI.

Since: 0.2.1.0

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

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

isPathAbsolute :: URI -> Bool Source #

Return True if path in a given URI is absolute.

Since: 0.1.0.0

relativeTo Source #

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 Source #

Authority component of URI.

Constructors

Authority 

Fields

Instances
Eq Authority Source # 
Instance details

Defined in Text.URI.Types

Methods

(==) :: Authority -> Authority -> Bool

(/=) :: Authority -> Authority -> Bool

Data Authority Source # 
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 :: (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

Ord Authority Source # 
Instance details

Defined in Text.URI.Types

Methods

compare :: Authority -> Authority -> Ordering

(<) :: Authority -> Authority -> Bool

(<=) :: Authority -> Authority -> Bool

(>) :: Authority -> Authority -> Bool

(>=) :: Authority -> Authority -> Bool

max :: Authority -> Authority -> Authority

min :: Authority -> Authority -> Authority

Show Authority Source # 
Instance details

Defined in Text.URI.Types

Methods

showsPrec :: Int -> Authority -> ShowS

show :: Authority -> String

showList :: [Authority] -> ShowS

Generic Authority Source # 
Instance details

Defined in Text.URI.Types

Associated Types

type Rep Authority :: Type -> Type

Methods

from :: Authority -> Rep Authority x

to :: Rep Authority x -> Authority

Lift Authority Source #

Since: 0.3.1.0

Instance details

Defined in Text.URI.Types

Methods

lift :: Authority -> Q Exp

NFData Authority Source # 
Instance details

Defined in Text.URI.Types

Methods

rnf :: Authority -> ()

Arbitrary Authority Source # 
Instance details

Defined in Text.URI.Types

type Rep Authority Source # 
Instance details

Defined in Text.URI.Types

type Rep Authority = D1 (MetaData "Authority" "Text.URI.Types" "modern-uri-0.3.1.0-8gVJU0yyGqqBmSEM0pAZya" 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 Source #

User info as a combination of username and password.

Constructors

UserInfo 

Fields

Instances
Eq UserInfo Source # 
Instance details

Defined in Text.URI.Types

Methods

(==) :: UserInfo -> UserInfo -> Bool

(/=) :: UserInfo -> UserInfo -> Bool

Data UserInfo Source # 
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 :: (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

Ord UserInfo Source # 
Instance details

Defined in Text.URI.Types

Methods

compare :: UserInfo -> UserInfo -> Ordering

(<) :: UserInfo -> UserInfo -> Bool

(<=) :: UserInfo -> UserInfo -> Bool

(>) :: UserInfo -> UserInfo -> Bool

(>=) :: UserInfo -> UserInfo -> Bool

max :: UserInfo -> UserInfo -> UserInfo

min :: UserInfo -> UserInfo -> UserInfo

Show UserInfo Source # 
Instance details

Defined in Text.URI.Types

Methods

showsPrec :: Int -> UserInfo -> ShowS

show :: UserInfo -> String

showList :: [UserInfo] -> ShowS

Generic UserInfo Source # 
Instance details

Defined in Text.URI.Types

Associated Types

type Rep UserInfo :: Type -> Type

Methods

from :: UserInfo -> Rep UserInfo x

to :: Rep UserInfo x -> UserInfo

Lift UserInfo Source #

Since: 0.3.1.0

Instance details

Defined in Text.URI.Types

Methods

lift :: UserInfo -> Q Exp

NFData UserInfo Source # 
Instance details

Defined in Text.URI.Types

Methods

rnf :: UserInfo -> ()

Arbitrary UserInfo Source # 
Instance details

Defined in Text.URI.Types

type Rep UserInfo Source # 
Instance details

Defined in Text.URI.Types

type Rep UserInfo = D1 (MetaData "UserInfo" "Text.URI.Types" "modern-uri-0.3.1.0-8gVJU0yyGqqBmSEM0pAZya" 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 Source #

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
Eq QueryParam Source # 
Instance details

Defined in Text.URI.Types

Methods

(==) :: QueryParam -> QueryParam -> Bool

(/=) :: QueryParam -> QueryParam -> Bool

Data QueryParam Source # 
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 :: (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

Ord QueryParam Source # 
Instance details

Defined in Text.URI.Types

Show QueryParam Source # 
Instance details

Defined in Text.URI.Types

Methods

showsPrec :: Int -> QueryParam -> ShowS

show :: QueryParam -> String

showList :: [QueryParam] -> ShowS

Generic QueryParam Source # 
Instance details

Defined in Text.URI.Types

Associated Types

type Rep QueryParam :: Type -> Type

Methods

from :: QueryParam -> Rep QueryParam x

to :: Rep QueryParam x -> QueryParam

Lift QueryParam Source #

Since: 0.3.1.0

Instance details

Defined in Text.URI.Types

Methods

lift :: QueryParam -> Q Exp

NFData QueryParam Source # 
Instance details

Defined in Text.URI.Types

Methods

rnf :: QueryParam -> ()

Arbitrary QueryParam Source # 
Instance details

Defined in Text.URI.Types

type Rep QueryParam Source # 
Instance details

Defined in Text.URI.Types

type Rep QueryParam = D1 (MetaData "QueryParam" "Text.URI.Types" "modern-uri-0.3.1.0-8gVJU0yyGqqBmSEM0pAZya" False) (C1 (MetaCons "QueryFlag" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RText QueryKey))) :+: C1 (MetaCons "QueryParam" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RText QueryKey)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RText QueryValue))))

newtype ParseException Source #

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
Eq ParseException Source # 
Instance details

Defined in Text.URI.Types

Data ParseException Source # 
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 :: (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

Show ParseException Source # 
Instance details

Defined in Text.URI.Types

Methods

showsPrec :: Int -> ParseException -> ShowS

show :: ParseException -> String

showList :: [ParseException] -> ShowS

Generic ParseException Source # 
Instance details

Defined in Text.URI.Types

Associated Types

type Rep ParseException :: Type -> Type

NFData ParseException Source # 
Instance details

Defined in Text.URI.Types

Methods

rnf :: ParseException -> ()

Exception ParseException Source # 
Instance details

Defined in Text.URI.Types

Methods

toException :: ParseException -> SomeException

fromException :: SomeException -> Maybe ParseException

displayException :: ParseException -> String

type Rep ParseException Source # 
Instance details

Defined in Text.URI.Types

type Rep ParseException = D1 (MetaData "ParseException" "Text.URI.Types" "modern-uri-0.3.1.0-8gVJU0yyGqqBmSEM0pAZya" True) (C1 (MetaCons "ParseException" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ParseErrorBundle Text 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) Source #

Refined text labelled at the type level.

Instances
Eq (RText l) Source # 
Instance details

Defined in Text.URI.Types

Methods

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

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

Typeable l => Data (RText l) Source # 
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 :: (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)

Ord (RText l) Source # 
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

Show (RText l) Source # 
Instance details

Defined in Text.URI.Types

Methods

showsPrec :: Int -> RText l -> ShowS

show :: RText l -> String

showList :: [RText l] -> ShowS

Generic (RText l) Source # 
Instance details

Defined in Text.URI.Types

Associated Types

type Rep (RText l) :: Type -> Type

Methods

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

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

Typeable l => Lift (RText l) Source #

Since: 0.3.1.0

Instance details

Defined in Text.URI.Types

Methods

lift :: RText l -> Q Exp

NFData (RText l) Source # 
Instance details

Defined in Text.URI.Types

Methods

rnf :: RText l -> ()

Arbitrary (RText Scheme) Source # 
Instance details

Defined in Text.URI.Types

Arbitrary (RText Host) Source # 
Instance details

Defined in Text.URI.Types

Methods

arbitrary :: Gen (RText Host)

shrink :: RText Host -> [RText Host]

Arbitrary (RText Username) Source # 
Instance details

Defined in Text.URI.Types

Arbitrary (RText Password) Source # 
Instance details

Defined in Text.URI.Types

Arbitrary (RText PathPiece) Source # 
Instance details

Defined in Text.URI.Types

Arbitrary (RText QueryKey) Source # 
Instance details

Defined in Text.URI.Types

Arbitrary (RText QueryValue) Source # 
Instance details

Defined in Text.URI.Types

Arbitrary (RText Fragment) Source # 
Instance details

Defined in Text.URI.Types

type Rep (RText l) Source # 
Instance details

Defined in Text.URI.Types

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

data RTextLabel Source #

Refined text labels.

Instances
Eq RTextLabel Source # 
Instance details

Defined in Text.URI.Types

Methods

(==) :: RTextLabel -> RTextLabel -> Bool

(/=) :: RTextLabel -> RTextLabel -> Bool

Data RTextLabel Source # 
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 :: (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

Ord RTextLabel Source # 
Instance details

Defined in Text.URI.Types

Show RTextLabel Source # 
Instance details

Defined in Text.URI.Types

Methods

showsPrec :: Int -> RTextLabel -> ShowS

show :: RTextLabel -> String

showList :: [RTextLabel] -> ShowS

Generic RTextLabel Source # 
Instance details

Defined in Text.URI.Types

Associated Types

type Rep RTextLabel :: Type -> Type

Methods

from :: RTextLabel -> Rep RTextLabel x

to :: Rep RTextLabel x -> RTextLabel

type Rep RTextLabel Source # 
Instance details

Defined in Text.URI.Types

type Rep RTextLabel = D1 (MetaData "RTextLabel" "Text.URI.Types" "modern-uri-0.3.1.0-8gVJU0yyGqqBmSEM0pAZya" 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) Source #

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) Source #

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) Source #

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) Source #

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) Source #

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) Source #

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) Source #

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) Source #

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 :: RText l -> Text Source #

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

data RTextException Source #

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
Eq RTextException Source # 
Instance details

Defined in Text.URI.Types

Data RTextException Source # 
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 :: (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

Ord RTextException Source # 
Instance details

Defined in Text.URI.Types

Show RTextException Source # 
Instance details

Defined in Text.URI.Types

Methods

showsPrec :: Int -> RTextException -> ShowS

show :: RTextException -> String

showList :: [RTextException] -> ShowS

Generic RTextException Source # 
Instance details

Defined in Text.URI.Types

Associated Types

type Rep RTextException :: Type -> Type

Exception RTextException Source # 
Instance details

Defined in Text.URI.Types

Methods

toException :: RTextException -> SomeException

fromException :: SomeException -> Maybe RTextException

displayException :: RTextException -> String

type Rep RTextException Source # 
Instance details

Defined in Text.URI.Types

type Rep RTextException = D1 (MetaData "RTextException" "Text.URI.Types" "modern-uri-0.3.1.0-8gVJU0yyGqqBmSEM0pAZya" 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 Source #

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 Source #

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 Source #

Render a given URI value as strict Text.

render' :: URI -> Builder Source #

Render a given URI value as a Builder.

renderBs :: URI -> ByteString Source #

Render a given URI value as a strict ByteString.

renderBs' :: URI -> Builder Source #

Render a given URI value as a Builder.

renderStr :: URI -> String Source #

Render a given URI value as a String.

Since: 0.0.2.0

renderStr' :: URI -> ShowS Source #

Render a given URI value as ShowS.

Since: 0.0.2.0