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

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

Text.URI

Contents

Description

This is 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 # 

Methods

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

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

Data URI Source # 

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 # 

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 # 

Methods

showsPrec :: Int -> URI -> ShowS #

show :: URI -> String #

showList :: [URI] -> ShowS #

Generic URI Source # 

Associated Types

type Rep URI :: * -> * #

Methods

from :: URI -> Rep URI x #

to :: Rep URI x -> URI #

Arbitrary URI Source # 

Methods

arbitrary :: Gen URI #

shrink :: URI -> [URI] #

NFData URI Source # 

Methods

rnf :: URI -> () #

type Rep URI Source # 

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

Construct a URI from Text. In case of failure ParseException is thrown.

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

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

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

data Authority Source #

Authority component of URI.

Constructors

Authority 

Fields

Instances

Eq Authority Source # 
Data Authority Source # 

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 # 
Show Authority Source # 
Generic Authority Source # 

Associated Types

type Rep Authority :: * -> * #

Arbitrary Authority Source # 
NFData Authority Source # 

Methods

rnf :: Authority -> () #

type Rep Authority Source # 
type Rep Authority = D1 (MetaData "Authority" "Text.URI.Types" "modern-uri-0.0.2.0-3B4qYg8VgJ14v3X8nSH5pH" False) (C1 (MetaCons "Authority" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "authUserInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe UserInfo))) ((:*:) (S1 (MetaSel (Just Symbol "authHost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RText Host))) (S1 (MetaSel (Just Symbol "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 # 
Data UserInfo Source # 

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 # 
Show UserInfo Source # 
Generic UserInfo Source # 

Associated Types

type Rep UserInfo :: * -> * #

Methods

from :: UserInfo -> Rep UserInfo x #

to :: Rep UserInfo x -> UserInfo #

Arbitrary UserInfo Source # 
NFData UserInfo Source # 

Methods

rnf :: UserInfo -> () #

type Rep UserInfo Source # 
type Rep UserInfo = D1 (MetaData "UserInfo" "Text.URI.Types" "modern-uri-0.0.2.0-3B4qYg8VgJ14v3X8nSH5pH" False) (C1 (MetaCons "UserInfo" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "uiUsername") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (RText Username))) (S1 (MetaSel (Just Symbol "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 # 
Data QueryParam Source # 

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 # 
Show QueryParam Source # 
Generic QueryParam Source # 

Associated Types

type Rep QueryParam :: * -> * #

Arbitrary QueryParam Source # 
NFData QueryParam Source # 

Methods

rnf :: QueryParam -> () #

type Rep QueryParam Source # 

data ParseException Source #

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

Constructors

ParseException Text (ParseError Char Void)

Arguments are: original input and parse error

Instances

Eq ParseException Source # 
Data ParseException Source # 

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

Associated Types

type Rep ParseException :: * -> * #

Exception ParseException Source # 
type Rep ParseException Source # 
type Rep ParseException = D1 (MetaData "ParseException" "Text.URI.Parser.Text" "modern-uri-0.0.2.0-3B4qYg8VgJ14v3X8nSH5pH" False) (C1 (MetaCons "ParseException" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ParseError Char 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 Source #

Refined text labelled at the type level.

Instances

Eq (RText l) Source # 

Methods

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

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

Typeable RTextLabel l => Data (RText l) Source # 

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 # 

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 # 

Methods

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

show :: RText l -> String #

showList :: [RText l] -> ShowS #

Generic (RText l) Source # 

Associated Types

type Rep (RText l) :: * -> * #

Methods

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

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

Arbitrary (RText Scheme) Source # 
Arbitrary (RText Host) Source # 
Arbitrary (RText Username) Source # 
Arbitrary (RText Password) Source # 
Arbitrary (RText PathPiece) Source # 
Arbitrary (RText QueryKey) Source # 
Arbitrary (RText QueryValue) Source # 
Arbitrary (RText Fragment) Source # 
NFData (RText l) Source # 

Methods

rnf :: RText l -> () #

type Rep (RText l) Source # 
type Rep (RText l) = D1 (MetaData "RText" "Text.URI.Types" "modern-uri-0.0.2.0-3B4qYg8VgJ14v3X8nSH5pH" True) (C1 (MetaCons "RText" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data RTextLabel Source #

Refined text labels.

Instances

Eq RTextLabel Source # 
Data RTextLabel Source # 

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 # 
Show RTextLabel Source # 
Generic RTextLabel Source # 

Associated Types

type Rep RTextLabel :: * -> * #

type Rep RTextLabel Source # 
type Rep RTextLabel = D1 (MetaData "RTextLabel" "Text.URI.Types" "modern-uri-0.0.2.0-3B4qYg8VgJ14v3X8nSH5pH" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Scheme" PrefixI False) U1) (C1 (MetaCons "Host" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Username" PrefixI False) U1) (C1 (MetaCons "Password" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "PathPiece" PrefixI False) U1) (C1 (MetaCons "QueryKey" PrefixI False) U1)) ((:+:) (C1 (MetaCons "QueryValue" PrefixI False) U1) (C1 (MetaCons "Fragment" PrefixI False) U1))))

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

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 # 
Show RTextException Source # 
Generic RTextException Source # 

Associated Types

type Rep RTextException :: * -> * #

Exception RTextException Source # 
type Rep RTextException Source # 
type Rep RTextException = D1 (MetaData "RTextException" "Text.URI.Types" "modern-uri-0.0.2.0-3B4qYg8VgJ14v3X8nSH5pH" False) (C1 (MetaCons "RTextException" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RTextLabel)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))

Parsing

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

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