dormouse-uri-0.3.0.0: Library for type-safe representations of Uri/Urls
Safe HaskellSafe-Inferred
LanguageHaskell2010

Dormouse.Uri

Synopsis

Documentation

data Authority Source #

The Authority component of a URI

Instances

Instances details
Show Authority Source # 
Instance details

Defined in Dormouse.Uri.Types

Eq Authority Source # 
Instance details

Defined in Dormouse.Uri.Types

Lift Authority Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

newtype Fragment Source #

The Fragment component of a URI

Constructors

Fragment 

Fields

Instances

Instances details
IsString Fragment Source # 
Instance details

Defined in Dormouse.Uri.Types

Show Fragment Source # 
Instance details

Defined in Dormouse.Uri.Types

Eq Fragment Source # 
Instance details

Defined in Dormouse.Uri.Types

Lift Fragment Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

newtype Host Source #

The Host subcomponent of a URI Authority

Constructors

Host 

Fields

Instances

Instances details
IsString Host Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

fromString :: String -> Host #

Show Host Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

showsPrec :: Int -> Host -> ShowS #

show :: Host -> String #

showList :: [Host] -> ShowS #

Eq Host Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

Lift Host Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

newtype Path (ref :: UriReferenceType) Source #

The Path component of a URI, including a series of individual Path Segments

Constructors

Path 

Fields

Instances

Instances details
Lift (Path ref :: Type) Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

lift :: Quote m => Path ref -> m Exp #

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

Show (Path ref) Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

showsPrec :: Int -> Path ref -> ShowS #

show :: Path ref -> String #

showList :: [Path ref] -> ShowS #

Eq (Path ref) Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

newtype PathSegment Source #

An individial Path segment of a URI

Constructors

PathSegment 

Fields

Instances

Instances details
IsString PathSegment Source # 
Instance details

Defined in Dormouse.Uri.Types

Show PathSegment Source # 
Instance details

Defined in Dormouse.Uri.Types

Eq PathSegment Source # 
Instance details

Defined in Dormouse.Uri.Types

Lift PathSegment Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

newtype Query Source #

The Query component of a URI

Constructors

Query 

Fields

Instances

Instances details
IsString Query Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

fromString :: String -> Query #

Show Query Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

Eq Query Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

Lift Query Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

newtype Scheme Source #

The Scheme component of a URI

Constructors

Scheme 

Fields

Instances

Instances details
Show Scheme Source # 
Instance details

Defined in Dormouse.Uri.Types

Eq Scheme Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

Lift Scheme Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

newtype UserInfo Source #

The UserInfo subcomponent of a URI Authority

Constructors

UserInfo 

Fields

Instances

Instances details
Show UserInfo Source # 
Instance details

Defined in Dormouse.Uri.Types

Eq UserInfo Source # 
Instance details

Defined in Dormouse.Uri.Types

Lift UserInfo Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

data Uri Source #

A Uniform Resource Identifier (URI) is a compact sequence of characters that identifies an abstract or physical resource. It is defined according to RFC 3986 (https://tools.ietf.org/html/rfc3986).

Instances

Instances details
Show Uri Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

showsPrec :: Int -> Uri -> ShowS #

show :: Uri -> String #

showList :: [Uri] -> ShowS #

Eq Uri Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

Lift Uri Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

data RelRef Source #

The data associated with a URI Relative Reference

Instances

Instances details
Show RelRef Source # 
Instance details

Defined in Dormouse.Uri.Types

Eq RelRef Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

Lift RelRef Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

data UriReference Source #

A URI-reference is either a URI or a relative reference. If the URI-reference's prefix does not match the syntax of a scheme followed by its colon separator, then the URI-reference is a relative reference.

Instances

Instances details
Show UriReference Source # 
Instance details

Defined in Dormouse.Uri.Types

Eq UriReference Source # 
Instance details

Defined in Dormouse.Uri.Types

Lift UriReference Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

parseUri :: MonadThrow m => ByteString -> m Uri Source #

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

parseUriRef :: MonadThrow m => ByteString -> m UriReference Source #

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