dormouse-uri-0.1.0.1: Library for type-safe representations of Uri/Urls
Safe HaskellNone
LanguageHaskell2010

Dormouse.Url

Synopsis

Documentation

data Url (scheme :: Symbol) where Source #

A Url is defined here as an absolute URI in the http or https schemes. Authority components are requried by the http / https Uri schemes.

Constructors

HttpUrl :: UrlComponents -> Url "http" 
HttpsUrl :: UrlComponents -> Url "https" 

Instances

Instances details
Lift (Url scheme :: Type) Source # 
Instance details

Defined in Dormouse.Url.Types

Methods

lift :: Url scheme -> Q Exp #

liftTyped :: Url scheme -> Q (TExp (Url scheme)) #

Eq (Url scheme) Source # 
Instance details

Defined in Dormouse.Url.Types

Methods

(==) :: Url scheme -> Url scheme -> Bool #

(/=) :: Url scheme -> Url scheme -> Bool #

Show (Url scheme) Source # 
Instance details

Defined in Dormouse.Url.Types

Methods

showsPrec :: Int -> Url scheme -> ShowS #

show :: Url scheme -> String #

showList :: [Url scheme] -> ShowS #

IsUrl (Url scheme) Source # 
Instance details

Defined in Dormouse.Url.Class

Methods

asAnyUrl :: Url scheme -> AnyUrl Source #

data AnyUrl Source #

AnyUrl is a wrapper aroud Url which allows either http or https urls.

Constructors

forall scheme. AnyUrl (Url scheme) 

Instances

Instances details
Eq AnyUrl Source # 
Instance details

Defined in Dormouse.Url.Types

Methods

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

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

Show AnyUrl Source # 
Instance details

Defined in Dormouse.Url.Types

IsUrl AnyUrl Source # 
Instance details

Defined in Dormouse.Url.Class

Lift AnyUrl Source # 
Instance details

Defined in Dormouse.Url.Types

Methods

lift :: AnyUrl -> Q Exp #

liftTyped :: AnyUrl -> Q (TExp AnyUrl) #

ensureHttp :: MonadThrow m => AnyUrl -> m (Url "http") Source #

Ensure that the supplied Url uses the _http_ scheme, throwing a UrlException in m if this is not the case

ensureHttps :: MonadThrow m => AnyUrl -> m (Url "https") Source #

Ensure that the supplied Url uses the _https_ scheme, throwing a UrlException in m if this is not the case

parseUrl :: MonadThrow m => ByteString -> m AnyUrl Source #

Parse an ascii ByteString as a url, throwing a UriException in m if this fails

parseHttpUrl :: MonadThrow m => ByteString -> m (Url "http") Source #

Parse an ascii ByteString as an http url, throwing a UriException in m if this fails

parseHttpsUrl :: MonadThrow m => ByteString -> m (Url "https") Source #

Parse an ascii ByteString as an https url, throwing a UriException in m if this fails

class (Eq url, Show url) => IsUrl url where Source #

Methods

asAnyUrl :: url -> AnyUrl Source #

Instances

Instances details
IsUrl AnyUrl Source # 
Instance details

Defined in Dormouse.Url.Class

IsUrl (Url scheme) Source # 
Instance details

Defined in Dormouse.Url.Class

Methods

asAnyUrl :: Url scheme -> AnyUrl Source #