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

Dormouse.Uri

Synopsis

Documentation

data Authority Source #

The Authority component of a URI

Instances

Instances details
Eq Authority Source # 
Instance details

Defined in Dormouse.Uri.Types

Show Authority Source # 
Instance details

Defined in Dormouse.Uri.Types

Lift Authority Source # 
Instance details

Defined in Dormouse.Uri.Types

newtype Fragment Source #

The Fragment component of a URI

Constructors

Fragment 

Fields

Instances

Instances details
Eq Fragment Source # 
Instance details

Defined in Dormouse.Uri.Types

Show Fragment Source # 
Instance details

Defined in Dormouse.Uri.Types

IsString Fragment Source # 
Instance details

Defined in Dormouse.Uri.Types

Lift Fragment Source # 
Instance details

Defined in Dormouse.Uri.Types

newtype Host Source #

The Host subcomponent of a URI Authority

Constructors

Host 

Fields

Instances

Instances details
Eq Host Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

Show Host Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

showsPrec :: Int -> Host -> ShowS #

show :: Host -> String #

showList :: [Host] -> ShowS #

IsString Host Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

fromString :: String -> Host #

Lift Host Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

lift :: Host -> Q Exp #

liftTyped :: Host -> Q (TExp 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 :: Path ref -> Q Exp #

liftTyped :: Path ref -> Q (TExp (Path ref)) #

Eq (Path ref) Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

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 #

newtype PathSegment Source #

An individial Path segment of a URI

Constructors

PathSegment 

Fields

Instances

Instances details
Eq PathSegment Source # 
Instance details

Defined in Dormouse.Uri.Types

Show PathSegment Source # 
Instance details

Defined in Dormouse.Uri.Types

IsString PathSegment Source # 
Instance details

Defined in Dormouse.Uri.Types

Lift PathSegment Source # 
Instance details

Defined in Dormouse.Uri.Types

newtype Query Source #

The Query component of a URI

Constructors

Query 

Fields

Instances

Instances details
Eq Query Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

Show Query Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

IsString Query Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

fromString :: String -> Query #

Lift Query Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

lift :: Query -> Q Exp #

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

newtype Scheme Source #

The Scheme component of a URI

Constructors

Scheme 

Fields

Instances

Instances details
Eq Scheme Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

Show Scheme Source # 
Instance details

Defined in Dormouse.Uri.Types

Lift Scheme Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

lift :: Scheme -> Q Exp #

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

newtype UserInfo Source #

The UserInfo subcomponent of a URI Authority

Constructors

UserInfo 

Fields

Instances

Instances details
Eq UserInfo Source # 
Instance details

Defined in Dormouse.Uri.Types

Show UserInfo Source # 
Instance details

Defined in Dormouse.Uri.Types

Lift UserInfo Source # 
Instance details

Defined in Dormouse.Uri.Types

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

Defined in Dormouse.Uri.Types

Methods

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

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

Show Uri Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

showsPrec :: Int -> Uri -> ShowS #

show :: Uri -> String #

showList :: [Uri] -> ShowS #

Lift Uri Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

lift :: Uri -> Q Exp #

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

data RelRef Source #

The data associated with a URI Relative Reference

Instances

Instances details
Eq RelRef Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

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

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

Show RelRef Source # 
Instance details

Defined in Dormouse.Uri.Types

Lift RelRef Source # 
Instance details

Defined in Dormouse.Uri.Types

Methods

lift :: RelRef -> Q Exp #

liftTyped :: RelRef -> Q (TExp 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
Eq UriReference Source # 
Instance details

Defined in Dormouse.Uri.Types

Show UriReference Source # 
Instance details

Defined in Dormouse.Uri.Types

Lift UriReference Source # 
Instance details

Defined in Dormouse.Uri.Types

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