uri-0.1.6.4: Library for working with URIs

Safe HaskellSafe
LanguageHaskell98

Text.URI

Synopsis

Documentation

data URI Source #

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 

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 #

dereferencePath :: [String] -> [String] Source #

Removes ".." and "." from path

dereferencePathString :: String -> String Source #

dereferencePath for strings

escapeString :: (Char -> Bool) -> String -> String Source #

Escapes string, using predicate to determine whether character is allowed

isReference :: URI -> Bool Source #

Checks if uri is a reference

isRelative :: URI -> Bool Source #

Checks if uri is relative

nullURI :: URI Source #

Blank URI

okInFragment :: Char -> Bool Source #

Checks if character is OK in fragment

okInPath :: Char -> Bool Source #

Checks if character is OK in path

okInPathSegment :: Char -> Bool Source #

Checks if character is ok in path segment

okInQuery :: Char -> Bool Source #

Checks if character is OK in query

okInQueryItem :: Char -> Bool Source #

Checks if character is OK in urlencoded query item

okInUserinfo :: Char -> Bool Source #

Checks if character is OK in userinfo

mergePaths :: [String] -> [String] -> [String] Source #

Merges two paths

mergePathStrings :: String -> String -> String Source #

mergePaths for strings

mergeURIs Source #

Arguments

:: URI

Base URI

-> URI

Reference URI

-> URI

Resulting URI

Merges two URIs

mergeURIStrings :: String -> String -> String Source #

mergeURIs for strings

pairsToQuery :: [(String, String)] -> String Source #

Composes www-urlencoded query from key-value pairs

parseURI :: String -> Maybe URI Source #

Parses URI

pathToSegments :: String -> [String] Source #

Splits path to segments

segmentsToPath :: [String] -> String Source #

Joins path segments, with escaping

queryToPairs :: String -> [(String, String)] Source #

Parses www-urlencoded string to key-value pairs

unescapeString :: String -> String Source #

Unescapes percent-sequences

uriPathSegments :: URI -> [String] Source #

Convenience function for extracting path segments

uriQueryItems :: URI -> [(String, String)] Source #

Convenience function for extracting www-urlencoded data