debian-4.0.5: Modules for working with the Debian package system
Safe HaskellSafe-Inferred
LanguageHaskell2010

Debian.URI

Synopsis

Documentation

uriToString :: (String -> String) -> URI -> ShowS #

Turn a URI into a string.

Uses a supplied function to map the userinfo part of the URI.

The Show instance for URI uses a mapping that hides any password that may be present in the URI. Use this function with argument id to preserve the password in the formatted output.

parseAbsoluteURI :: String -> Maybe URI #

Parse an absolute URI to a URI value. Returns Nothing if the string is not a valid absolute URI. (an absolute URI without a fragment identifier).

parseRelativeReference :: String -> Maybe URI #

Parse a relative URI to a URI value. Returns Nothing if the string is not a valid relative URI. (a relative URI with optional fragment identifier).

parseURIReference :: String -> Maybe URI #

Parse a URI reference to a URI value. Returns Nothing if the string is not a valid URI reference. (an absolute or relative URI with optional fragment identifier).

parseURI :: String -> Maybe URI #

Turn a string containing a URI into a URI. Returns Nothing if the string is not a valid URI; (an absolute URI with optional fragment identifier).

NOTE: this is different from the previous network.URI, whose parseURI function works like parseURIReference in this module.

nullURI :: URI #

Blank URI

data URI #

Represents a general universal resource identifier using its component parts.

For example, for the URI

  foo://anonymous@www.haskell.org:42/ghc?query#frag

the components are:

Constructors

URI 

Fields

Instances

Instances details
Data URI 
Instance details

Defined in Network.URI

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 :: forall r r'. (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 #

Generic URI 
Instance details

Defined in Network.URI

Associated Types

type Rep URI :: Type -> Type #

Methods

from :: URI -> Rep URI x #

to :: Rep URI x -> URI #

Show URI 
Instance details

Defined in Network.URI

Methods

showsPrec :: Int -> URI -> ShowS #

show :: URI -> String #

showList :: [URI] -> ShowS #

NFData URI 
Instance details

Defined in Network.URI

Methods

rnf :: URI -> () #

Eq URI 
Instance details

Defined in Network.URI

Methods

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

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

Ord URI 
Instance details

Defined in Network.URI

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 #

Lift URI 
Instance details

Defined in Network.URI

Methods

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

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

type Rep URI 
Instance details

Defined in Network.URI

data URIAuth #

Type for authority value within a URI

Constructors

URIAuth 

Fields

Instances

Instances details
Data URIAuth 
Instance details

Defined in Network.URI

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> URIAuth -> c URIAuth #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c URIAuth #

toConstr :: URIAuth -> Constr #

dataTypeOf :: URIAuth -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c URIAuth) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c URIAuth) #

gmapT :: (forall b. Data b => b -> b) -> URIAuth -> URIAuth #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> URIAuth -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> URIAuth -> r #

gmapQ :: (forall d. Data d => d -> u) -> URIAuth -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> URIAuth -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> URIAuth -> m URIAuth #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> URIAuth -> m URIAuth #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> URIAuth -> m URIAuth #

Generic URIAuth 
Instance details

Defined in Network.URI

Associated Types

type Rep URIAuth :: Type -> Type #

Methods

from :: URIAuth -> Rep URIAuth x #

to :: Rep URIAuth x -> URIAuth #

Show URIAuth 
Instance details

Defined in Network.URI

NFData URIAuth 
Instance details

Defined in Network.URI

Methods

rnf :: URIAuth -> () #

Eq URIAuth 
Instance details

Defined in Network.URI

Methods

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

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

Ord URIAuth 
Instance details

Defined in Network.URI

Lift URIAuth 
Instance details

Defined in Network.URI

Methods

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

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

type Rep URIAuth 
Instance details

Defined in Network.URI

type Rep URIAuth = D1 ('MetaData "URIAuth" "Network.URI" "network-uri-2.6.4.2-HOWkOsJ6iQ9LdZ2sAMVHdr" 'False) (C1 ('MetaCons "URIAuth" 'PrefixI 'True) (S1 ('MetaSel ('Just "uriUserInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "uriRegName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "uriPort") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))

data URIError Source #

Instances

Instances details
Show URIError Source # 
Instance details

Defined in Debian.URI

HasURIError URIError Source # 
Instance details

Defined in Debian.URI

Eq URIError Source # 
Instance details

Defined in Debian.URI

Ord URIError Source # 
Instance details

Defined in Debian.URI

String known to parsable by parseURIReference. Mainly

newtype URI' Source #

A wrapper around a String containing a known parsable URI. Not absolutely safe, because you could say read "URI' "bogus string"" :: URI'. But enough to save me from myself.

Constructors

URI' String 

Instances

Instances details
Read URI' Source # 
Instance details

Defined in Debian.URI

Show URI' Source # 
Instance details

Defined in Debian.URI

Methods

showsPrec :: Int -> URI' -> ShowS #

show :: URI' -> String #

showList :: [URI'] -> ShowS #

Eq URI' Source # 
Instance details

Defined in Debian.URI

Methods

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

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

Ord URI' Source # 
Instance details

Defined in Debian.URI

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

toURI' :: URI -> URI' Source #

Using the bogus Show instance of URI here. If it ever gets fixed this will stop working. Worth noting that show will obscure any password info embedded in the URI, so that's nice.

parseURI' :: (HasURIError e, MonadError e m) => String -> m URI Source #

parseURI with MonadError

appendURI :: MonadError URIError m => URI -> URI -> m URI Source #

Conservative appending of absolute and relative URIs. There may be other cases that can be implemented, lets see if they turn up.

appendURIs :: (Foldable t, MonadError URIError m) => t URI -> m URI Source #

Append a list of URI @@ λ> appendURIs (parseURI "http://host.com") (parseURIRelative "/bar")

Lift IO operations into a MonadError instance

class HasParseError e where Source #

Instances

Instances details
HasParseError ParseError Source # 
Instance details

Defined in Debian.URI

class HasURIError e where Source #

Methods

fromURIError :: URIError -> e Source #

Instances

Instances details
HasURIError URIError Source # 
Instance details

Defined in Debian.URI

QuickCheck properties

Orphan instances