{-# LANGUAGE RecordWildCards, CPP #-}
#if __GLASGOW_HASKELL__ >= 800
{-# LANGUAGE DeriveLift, StandaloneDeriving #-}
#else
{-# LANGUAGE TemplateHaskell #-}
#endif
#if MIN_VERSION_template_haskell(2,12,0) && MIN_VERSION_parsec(3,13,0)
{-# LANGUAGE Safe #-}
#elif __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
module Network.URI
(
URI(..)
, URIAuth(..)
, nullURI
, nullURIAuth
, rectify, rectifyAuth
, parseURI
, parseURIReference
, parseRelativeReference
, parseAbsoluteURI
, isURI
, isURIReference
, isRelativeReference
, isAbsoluteURI
, isIPv6address
, isIPv4address
, uriIsAbsolute
, uriIsRelative
, relativeTo
, nonStrictRelativeTo
, relativeFrom
, uriToString, uriAuthToString
, isReserved, isUnreserved
, isAllowedInURI, isUnescapedInURI
, isUnescapedInURIComponent
, escapeURIChar
, escapeURIString
, unEscapeString
, pathSegments
, normalizeCase
, normalizeEscape
, normalizePathSegments
, parseabsoluteURI
, escapeString
, reserved, unreserved
, scheme, authority, path, query, fragment
) where
import Text.ParserCombinators.Parsec
( GenParser, ParseError
, parse, (<?>), try
, option, many1, count, notFollowedBy
, char, satisfy, oneOf, string, eof
, unexpected
)
import Control.Applicative
import Control.Monad (MonadPlus(..))
import Control.DeepSeq (NFData(rnf), deepseq)
import Data.Char (ord, chr, isHexDigit, toLower, toUpper, digitToInt)
import Data.Bits ((.|.),(.&.),shiftL,shiftR)
import Data.List (unfoldr, isPrefixOf, isSuffixOf)
import Numeric (showIntAtBase)
import Language.Haskell.TH.Syntax (Lift(..))
#if !MIN_VERSION_base(4,8,0)
import Data.Traversable (sequenceA)
#endif
import Data.Typeable (Typeable)
#if MIN_VERSION_base(4,0,0)
import Data.Data (Data)
#else
import Data.Generics (Data)
#endif
#if __GLASGOW_HASKELL__ >= 702
import GHC.Generics (Generic)
#endif
data URI = URI
{ uriScheme :: String
, uriAuthority :: Maybe URIAuth
, uriPath :: String
, uriQuery :: String
, uriFragment :: String
#if __GLASGOW_HASKELL__ >= 702
} deriving (Eq, Ord, Typeable, Data, Generic)
#else
} deriving (Eq, Ord, Typeable, Data)
#endif
ensurePrefix :: String -> String -> String
ensurePrefix p s = if isPrefixOf p s then s else p ++ s
ensureSuffix :: String -> String -> String
ensureSuffix p s = if isSuffixOf p s then s else s ++ p
rectifyAuth :: URIAuth -> URIAuth
rectifyAuth a = URIAuth {
uriUserInfo = unlessEmpty (ensureSuffix "@") (uriUserInfo a),
uriRegName = uriRegName a,
uriPort = unlessEmpty (ensurePrefix ":") (uriPort a)
}
rectify :: URI -> URI
rectify u = URI {
uriScheme = ensureSuffix ":" (uriScheme u),
uriAuthority = fmap rectifyAuth (uriAuthority u),
uriPath = uriPath u,
uriQuery = unlessEmpty (ensurePrefix "?") (uriQuery u),
uriFragment = unlessEmpty (ensurePrefix "#") (uriFragment u)
}
unlessEmpty :: ([a] -> [a]) -> [a] -> [a]
unlessEmpty _f [] = []
unlessEmpty f x = f x
instance NFData URI where
rnf (URI s a p q f)
= s `deepseq` a `deepseq` p `deepseq` q `deepseq` f `deepseq` ()
data URIAuth = URIAuth
{ uriUserInfo :: String
, uriRegName :: String
, uriPort :: String
#if __GLASGOW_HASKELL__ >= 702
} deriving (Eq, Ord, Show, Typeable, Data, Generic)
#else
} deriving (Eq, Ord, Show, Typeable, Data)
#endif
instance NFData URIAuth where
rnf (URIAuth ui rn p) = ui `deepseq` rn `deepseq` p `deepseq` ()
nullURI :: URI
nullURI = URI
{ uriScheme = ""
, uriAuthority = Nothing
, uriPath = ""
, uriQuery = ""
, uriFragment = ""
}
nullURIAuth :: URIAuth
nullURIAuth = URIAuth
{ uriUserInfo = ""
, uriRegName = ""
, uriPort = ""
}
instance Show URI where
showsPrec _ = uriToString defaultUserInfoMap
defaultUserInfoMap :: String -> String
defaultUserInfoMap uinf = user++newpass
where
(user,pass) = break (==':') uinf
newpass = if null pass || (pass == "@")
|| (pass == ":@")
then pass
else ":...@"
parseURI :: String -> Maybe URI
parseURI = parseURIAny uri
parseURIReference :: String -> Maybe URI
parseURIReference = parseURIAny uriReference
parseRelativeReference :: String -> Maybe URI
parseRelativeReference = parseURIAny relativeRef
parseAbsoluteURI :: String -> Maybe URI
parseAbsoluteURI = parseURIAny absoluteURI
isURI :: String -> Bool
isURI = isValidParse uri
isURIReference :: String -> Bool
isURIReference = isValidParse uriReference
isRelativeReference :: String -> Bool
isRelativeReference = isValidParse relativeRef
isAbsoluteURI :: String -> Bool
isAbsoluteURI = isValidParse absoluteURI
isIPv6address :: String -> Bool
isIPv6address = isValidParse ipv6address
isIPv4address :: String -> Bool
isIPv4address = isValidParse ipv4address
parseURIAny :: URIParser URI -> String -> Maybe URI
parseURIAny parser uristr = case parseAll parser "" uristr of
Left _ -> Nothing
Right u -> Just u
isValidParse :: URIParser a -> String -> Bool
isValidParse parser uristr = case parseAll parser "" uristr of
Left _ -> False
Right _ -> True
parseAll :: URIParser a -> String -> String -> Either ParseError a
parseAll parser filename uristr = parse newparser filename uristr
where
newparser =
do { res <- parser
; eof
; return res
}
uriIsAbsolute :: URI -> Bool
uriIsAbsolute (URI {uriScheme = scheme'}) = scheme' /= ""
uriIsRelative :: URI -> Bool
uriIsRelative = not . uriIsAbsolute
type URIParser a = GenParser Char () a
escaped :: URIParser String
escaped = sequenceA [char '%', hexDigitChar, hexDigitChar]
isReserved :: Char -> Bool
isReserved c = isGenDelims c || isSubDelims c
isGenDelims :: Char -> Bool
isGenDelims c =
case c of
':' -> True
'/' -> True
'?' -> True
'#' -> True
'[' -> True
']' -> True
'@' -> True
_ -> False
isSubDelims :: Char -> Bool
isSubDelims c =
case c of
'!' -> True
'$' -> True
'&' -> True
'\'' -> True
'(' -> True
')' -> True
'*' -> True
'+' -> True
',' -> True
';' -> True
'=' -> True
_ -> False
subDelims :: URIParser String
subDelims = (:[]) <$> oneOf "!$&'()*+,;="
isUnreserved :: Char -> Bool
isUnreserved c = isAlphaNumChar c || (c `elem` "-_.~")
unreservedChar :: URIParser String
unreservedChar = (:[]) <$> satisfy isUnreserved
uri :: URIParser URI
uri =
do { us <- try uscheme
; (ua,up) <- hierPart
; uq <- option "" ( do { _ <- char '?' ; uquery } )
; uf <- option "" ( do { _ <- char '#' ; ufragment } )
; return $ URI
{ uriScheme = us
, uriAuthority = ua
, uriPath = up
, uriQuery = uq
, uriFragment = uf
}
}
hierPart :: URIParser ((Maybe URIAuth),String)
hierPart =
do { _ <- try (string "//")
; ua <- uauthority
; up <- pathAbEmpty
; return (ua,up)
}
<|> do { up <- pathAbs
; return (Nothing,up)
}
<|> do { up <- pathRootLess
; return (Nothing,up)
}
<|> do { return (Nothing,"")
}
uscheme :: URIParser String
uscheme =
do { s <- oneThenMany alphaChar (satisfy isSchemeChar)
; _ <- char ':'
; return $ s++":"
}
uauthority :: URIParser (Maybe URIAuth)
uauthority =
do { uu <- option "" (try userinfo)
; uh <- host
; up <- option "" port
; return $ Just $ URIAuth
{ uriUserInfo = uu
, uriRegName = uh
, uriPort = up
}
}
userinfo :: URIParser String
userinfo =
do { uu <- many (uchar ";:&=+$,")
; _ <- char '@'
; return (concat uu ++"@")
}
host :: URIParser String
host = ipLiteral <|> try ipv4address <|> regName
ipLiteral :: URIParser String
ipLiteral =
do { _ <- char '['
; ua <- ( ipv6addrz <|> ipvFuture )
; _ <- char ']'
; return $ "[" ++ ua ++ "]"
}
<?> "IP address literal"
ipvFuture :: URIParser String
ipvFuture =
do { _ <- char 'v'
; h <- hexDigitChar
; _ <- char '.'
; a <- many1 (satisfy isIpvFutureChar)
; return $ 'v':h:'.':a
}
isIpvFutureChar :: Char -> Bool
isIpvFutureChar c = isUnreserved c || isSubDelims c || (c==';')
zoneid :: URIParser String
zoneid = concat <$> many1 (unreservedChar <|> escaped)
ipv6addrz :: URIParser String
ipv6addrz = (++) <$> ipv6address <*> option "" (try $ (++) <$> string "%25" <*> zoneid)
ipv6address :: URIParser String
ipv6address =
try ( do
{ a2 <- count 6 h4c
; a3 <- ls32
; return $ concat a2 ++ a3
} )
<|> try ( do
{ _ <- string "::"
; a2 <- count 5 h4c
; a3 <- ls32
; return $ "::" ++ concat a2 ++ a3
} )
<|> try ( do
{ a1 <- opt_n_h4c_h4 0
; _ <- string "::"
; a2 <- count 4 h4c
; a3 <- ls32
; return $ a1 ++ "::" ++ concat a2 ++ a3
} )
<|> try ( do
{ a1 <- opt_n_h4c_h4 1
; _ <- string "::"
; a2 <- count 3 h4c
; a3 <- ls32
; return $ a1 ++ "::" ++ concat a2 ++ a3
} )
<|> try ( do
{ a1 <- opt_n_h4c_h4 2
; _ <- string "::"
; a2 <- count 2 h4c
; a3 <- ls32
; return $ a1 ++ "::" ++ concat a2 ++ a3
} )
<|> try ( do
{ a1 <- opt_n_h4c_h4 3
; _ <- string "::"
; a2 <- h4c
; a3 <- ls32
; return $ a1 ++ "::" ++ a2 ++ a3
} )
<|> try ( do
{ a1 <- opt_n_h4c_h4 4
; _ <- string "::"
; a3 <- ls32
; return $ a1 ++ "::" ++ a3
} )
<|> try ( do
{ a1 <- opt_n_h4c_h4 5
; _ <- string "::"
; a3 <- h4
; return $ a1 ++ "::" ++ a3
} )
<|> try ( do
{ a1 <- opt_n_h4c_h4 6
; _ <- string "::"
; return $ a1 ++ "::"
} )
<?> "IPv6 address"
opt_n_h4c_h4 :: Int -> URIParser String
opt_n_h4c_h4 n = option "" $
do { a1 <- countMinMax 0 n h4c
; a2 <- h4
; return $ concat a1 ++ a2
}
ls32 :: URIParser String
ls32 = try ( do
{ a1 <- h4c
; a2 <- h4
; return (a1++a2)
} )
<|> ipv4address
h4c :: URIParser String
h4c = try $
do { a1 <- h4
; _ <- char ':'
; _ <- notFollowedBy (char ':')
; return $ a1 ++ ":"
}
h4 :: URIParser String
h4 = countMinMax 1 4 hexDigitChar
ipv4address :: URIParser String
ipv4address =
do { a1 <- decOctet ; _ <- char '.'
; a2 <- decOctet ; _ <- char '.'
; a3 <- decOctet ; _ <- char '.'
; a4 <- decOctet
; _ <- notFollowedBy nameChar
; return $ a1++"."++a2++"."++a3++"."++a4
}
<?> "IPv4 Address"
decOctet :: URIParser String
decOctet =
do { a1 <- countMinMax 1 3 digitChar
; if (read a1 :: Integer) > 255 then
fail "Decimal octet value too large"
else
return a1
}
regName :: URIParser String
regName =
do { ss <- countMinMax 0 255 nameChar
; return $ concat ss
}
<?> "Registered name"
nameChar :: URIParser String
nameChar = (unreservedChar <|> escaped <|> subDelims)
<?> "Name character"
port :: URIParser String
port =
do { _ <- char ':'
; p <- many digitChar
; return (':':p)
}
pathAbEmpty :: URIParser String
pathAbEmpty =
do { ss <- many slashSegment
; return $ concat ss
}
pathAbs :: URIParser String
pathAbs =
do { _ <- char '/'
; ss <- option "" pathRootLess
; return $ '/':ss
}
pathNoScheme :: URIParser String
pathNoScheme =
do { s1 <- segmentNzc
; ss <- many slashSegment
; return $ concat (s1:ss)
}
pathRootLess :: URIParser String
pathRootLess =
do { s1 <- segmentNz
; ss <- many slashSegment
; return $ concat (s1:ss)
}
slashSegment :: URIParser String
slashSegment =
do { _ <- char '/'
; s <- segment
; return ('/':s)
}
segment :: URIParser String
segment =
do { ps <- many pchar
; return $ concat ps
}
segmentNz :: URIParser String
segmentNz =
do { ps <- many1 pchar
; return $ concat ps
}
segmentNzc :: URIParser String
segmentNzc =
do { ps <- many1 (uchar "@")
; return $ concat ps
}
pchar :: URIParser String
pchar = uchar ":@"
uchar :: String -> URIParser String
uchar extras =
unreservedChar
<|> escaped
<|> subDelims
<|> do { c <- oneOf extras ; return [c] }
uquery :: URIParser String
uquery =
do { ss <- many $ uchar (":@"++"/?")
; return $ '?':concat ss
}
ufragment :: URIParser String
ufragment =
do { ss <- many $ uchar (":@"++"/?")
; return $ '#':concat ss
}
uriReference :: URIParser URI
uriReference = uri <|> relativeRef
relativeRef :: URIParser URI
relativeRef =
do { notMatching uscheme
; (ua,up) <- relativePart
; uq <- option "" ( do { _ <- char '?' ; uquery } )
; uf <- option "" ( do { _ <- char '#' ; ufragment } )
; return $ URI
{ uriScheme = ""
, uriAuthority = ua
, uriPath = up
, uriQuery = uq
, uriFragment = uf
}
}
relativePart :: URIParser ((Maybe URIAuth),String)
relativePart =
do { _ <- try (string "//")
; ua <- uauthority
; up <- pathAbEmpty
; return (ua,up)
}
<|> do { up <- pathAbs
; return (Nothing,up)
}
<|> do { up <- pathNoScheme
; return (Nothing,up)
}
<|> do { return (Nothing,"")
}
absoluteURI :: URIParser URI
absoluteURI =
do { us <- uscheme
; (ua,up) <- hierPart
; uq <- option "" ( do { _ <- char '?' ; uquery } )
; return $ URI
{ uriScheme = us
, uriAuthority = ua
, uriPath = up
, uriQuery = uq
, uriFragment = ""
}
}
isAlphaChar :: Char -> Bool
isAlphaChar c = (c >= 'A' && c <= 'Z') || (c >= 'a' && c <= 'z')
isDigitChar :: Char -> Bool
isDigitChar c = (c >= '0' && c <= '9')
isAlphaNumChar :: Char -> Bool
isAlphaNumChar c = isAlphaChar c || isDigitChar c
isHexDigitChar :: Char -> Bool
isHexDigitChar c = isHexDigit c
isSchemeChar :: Char -> Bool
isSchemeChar c = (isAlphaNumChar c) || (c `elem` "+-.")
alphaChar :: URIParser Char
alphaChar = satisfy isAlphaChar
digitChar :: URIParser Char
digitChar = satisfy isDigitChar
hexDigitChar :: URIParser Char
hexDigitChar = satisfy isHexDigitChar
oneThenMany :: GenParser t s a -> GenParser t s a -> GenParser t s [a]
oneThenMany p1 pr =
do { a1 <- p1
; ar <- many pr
; return (a1:ar)
}
countMinMax :: Int -> Int -> GenParser t s a -> GenParser t s [a]
countMinMax m n p | m > 0 =
do { a1 <- p
; ar <- countMinMax (m-1) (n-1) p
; return (a1:ar)
}
countMinMax _ n _ | n <= 0 = return []
countMinMax _ n p = option [] $
do { a1 <- p
; ar <- countMinMax 0 (n-1) p
; return (a1:ar)
}
notMatching :: Show a => GenParser tok st a -> GenParser tok st ()
notMatching p = do { a <- try p ; unexpected (show a) } <|> return ()
uriToString :: (String->String) -> URI -> ShowS
uriToString userinfomap URI { uriScheme=myscheme
, uriAuthority=myauthority
, uriPath=mypath
, uriQuery=myquery
, uriFragment=myfragment
} =
(myscheme++) . (uriAuthToString userinfomap myauthority)
. (mypath++) . (myquery++) . (myfragment++)
uriAuthToString :: (String->String) -> (Maybe URIAuth) -> ShowS
uriAuthToString _ Nothing = id
uriAuthToString userinfomap
(Just URIAuth { uriUserInfo = myuinfo
, uriRegName = myregname
, uriPort = myport
} ) =
("//"++) . (if null myuinfo then id else ((userinfomap myuinfo)++))
. (myregname++)
. (myport++)
isAllowedInURI :: Char -> Bool
isAllowedInURI c = isReserved c || isUnreserved c || c == '%'
isUnescapedInURI :: Char -> Bool
isUnescapedInURI c = isReserved c || isUnreserved c
isUnescapedInURIComponent :: Char -> Bool
isUnescapedInURIComponent c = not (isReserved c || not (isUnescapedInURI c))
escapeURIChar :: (Char->Bool) -> Char -> String
escapeURIChar p c
| p c = [c]
| otherwise = concatMap (\i -> '%' : myShowHex i "") (utf8EncodeChar c)
where
myShowHex :: Int -> ShowS
myShowHex n r = case showIntAtBase 16 (toChrHex) n r of
[] -> "00"
[x] -> ['0',x]
cs -> cs
toChrHex d
| d < 10 = chr (ord '0' + fromIntegral d)
| otherwise = chr (ord 'A' + fromIntegral (d - 10))
utf8EncodeChar :: Char -> [Int]
utf8EncodeChar = map fromIntegral . go . ord
where
go oc
| oc <= 0x7f = [oc]
| oc <= 0x7ff = [ 0xc0 + (oc `shiftR` 6)
, 0x80 + oc .&. 0x3f
]
| oc <= 0xffff = [ 0xe0 + (oc `shiftR` 12)
, 0x80 + ((oc `shiftR` 6) .&. 0x3f)
, 0x80 + oc .&. 0x3f
]
| otherwise = [ 0xf0 + (oc `shiftR` 18)
, 0x80 + ((oc `shiftR` 12) .&. 0x3f)
, 0x80 + ((oc `shiftR` 6) .&. 0x3f)
, 0x80 + oc .&. 0x3f
]
escapeURIString
:: (Char->Bool)
-> String
-> String
escapeURIString p s = concatMap (escapeURIChar p) s
unEscapeString :: String -> String
unEscapeString [] = ""
unEscapeString s@(c:cs) = case unEscapeByte s of
Just (byte, rest) -> unEscapeUtf8 byte rest
Nothing -> c : unEscapeString cs
unEscapeByte :: String -> Maybe (Int, String)
unEscapeByte ('%':x1:x2:s) | isHexDigit x1 && isHexDigit x2 =
Just (digitToInt x1 * 16 + digitToInt x2, s)
unEscapeByte _ = Nothing
unEscapeUtf8 :: Int -> String -> String
unEscapeUtf8 c rest
| c < 0x80 = chr c : unEscapeString rest
| c < 0xc0 = replacement_character : unEscapeString rest
| c < 0xe0 = multi1
| c < 0xf0 = multi_byte 2 0xf 0x800
| c < 0xf8 = multi_byte 3 0x7 0x10000
| c < 0xfc = multi_byte 4 0x3 0x200000
| c < 0xfe = multi_byte 5 0x1 0x4000000
| otherwise = replacement_character : unEscapeString rest
where
replacement_character = '\xfffd'
multi1 = case unEscapeByte rest of
Just (c1, ds) | c1 .&. 0xc0 == 0x80 ->
let d = ((fromEnum c .&. 0x1f) `shiftL` 6) .|. fromEnum (c1 .&. 0x3f)
in if d >= 0x000080 then toEnum d : unEscapeString ds
else replacement_character : unEscapeString ds
_ -> replacement_character : unEscapeString rest
multi_byte :: Int -> Int -> Int -> String
multi_byte i mask overlong =
aux i rest (unEscapeByte rest) (c .&. mask)
where
aux 0 rs _ acc
| overlong <= acc && acc <= 0x10ffff &&
(acc < 0xd800 || 0xdfff < acc) &&
(acc < 0xfffe || 0xffff < acc) = chr acc : unEscapeString rs
| otherwise = replacement_character : unEscapeString rs
aux n _ (Just (r, rs)) acc
| r .&. 0xc0 == 0x80 = aux (n-1) rs (unEscapeByte rs)
$! shiftL acc 6 .|. (r .&. 0x3f)
aux _ rs _ _ = replacement_character : unEscapeString rs
nonStrictRelativeTo :: URI -> URI -> URI
nonStrictRelativeTo ref base = relativeTo ref' base
where
ref' = if uriScheme ref == uriScheme base
then ref { uriScheme="" }
else ref
isDefined :: ( MonadPlus m, Eq (m a) ) => m a -> Bool
isDefined a = a /= mzero
relativeTo :: URI -> URI -> URI
relativeTo ref base
| isDefined ( uriScheme ref ) =
just_segments ref
| isDefined ( uriAuthority ref ) =
just_segments ref { uriScheme = uriScheme base }
| isDefined ( uriPath ref ) =
if (head (uriPath ref) == '/') then
just_segments ref
{ uriScheme = uriScheme base
, uriAuthority = uriAuthority base
}
else
just_segments ref
{ uriScheme = uriScheme base
, uriAuthority = uriAuthority base
, uriPath = mergePaths base ref
}
| isDefined ( uriQuery ref ) =
just_segments ref
{ uriScheme = uriScheme base
, uriAuthority = uriAuthority base
, uriPath = uriPath base
}
| otherwise =
just_segments ref
{ uriScheme = uriScheme base
, uriAuthority = uriAuthority base
, uriPath = uriPath base
, uriQuery = uriQuery base
}
where
just_segments u =
u { uriPath = removeDotSegments (uriPath u) }
mergePaths b r
| isDefined (uriAuthority b) && null pb = '/':pr
| otherwise = dropLast pb ++ pr
where
pb = uriPath b
pr = uriPath r
dropLast = fst . splitLast
removeDotSegments :: String -> String
removeDotSegments ('/':ps) = '/':elimDots ps []
removeDotSegments ps = elimDots ps []
elimDots :: String -> [String] -> String
elimDots [] [] = ""
elimDots [] rs = concat (reverse rs)
elimDots ( '.':'/':ps) rs = elimDots ps rs
elimDots ( '.':[] ) rs = elimDots [] rs
elimDots ( '.':'.':'/':ps) rs = elimDots ps (drop 1 rs)
elimDots ( '.':'.':[] ) rs = elimDots [] (drop 1 rs)
elimDots ps rs = elimDots ps1 (r:rs)
where
(r,ps1) = nextSegment ps
nextSegment :: String -> (String,String)
nextSegment ps =
case break (=='/') ps of
(r,'/':ps1) -> (r++"/",ps1)
(r,_) -> (r,[])
segments :: String -> [String]
segments str = dropLeadingEmpty $ unfoldr nextSegmentMaybe str
where
nextSegmentMaybe "" = Nothing
nextSegmentMaybe ps =
case break (=='/') ps of
(seg, '/':ps1) -> Just (seg, ps1)
(seg, _) -> Just (seg, "")
dropLeadingEmpty ("":xs) = xs
dropLeadingEmpty xs = xs
pathSegments :: URI -> [String]
pathSegments = segments . uriPath
splitLast :: String -> (String,String)
splitLast p = (reverse revpath,reverse revname)
where
(revname,revpath) = break (=='/') $ reverse p
relativeFrom :: URI -> URI -> URI
relativeFrom uabs base
| diff uriScheme uabs base = uabs
| diff uriAuthority uabs base = uabs { uriScheme = "" }
| diff uriPath uabs base = uabs
{ uriScheme = ""
, uriAuthority = Nothing
, uriPath = relPathFrom (removeBodyDotSegments $ uriPath uabs)
(removeBodyDotSegments $ uriPath base)
}
| diff uriQuery uabs base = uabs
{ uriScheme = ""
, uriAuthority = Nothing
, uriPath = ""
}
| otherwise = uabs
{ uriScheme = ""
, uriAuthority = Nothing
, uriPath = ""
, uriQuery = ""
}
where
diff :: Eq b => (a -> b) -> a -> a -> Bool
diff sel u1 u2 = sel u1 /= sel u2
removeBodyDotSegments p = removeDotSegments p1 ++ p2
where
(p1,p2) = splitLast p
relPathFrom :: String -> String -> String
relPathFrom [] _ = "/"
relPathFrom pabs [] = pabs
relPathFrom pabs base =
if sa1 == sb1
then if (sa1 == "/")
then if (sa2 == sb2)
then relPathFrom1 ra2 rb2
else
pabs
else relPathFrom1 ra1 rb1
else pabs
where
(sa1,ra1) = nextSegment pabs
(sb1,rb1) = nextSegment base
(sa2,ra2) = nextSegment ra1
(sb2,rb2) = nextSegment rb1
relPathFrom1 :: String -> String -> String
relPathFrom1 pabs base = relName
where
(sa,na) = splitLast pabs
(sb,nb) = splitLast base
rp = relSegsFrom sa sb
relName = if null rp then
if (na == nb) then ""
else if protect na then "./"++na
else na
else
rp++na
protect s = null s || ':' `elem` s
relSegsFrom :: String -> String -> String
relSegsFrom [] [] = ""
relSegsFrom sabs base =
if sa1 == sb1
then relSegsFrom ra1 rb1
else difSegsFrom sabs base
where
(sa1,ra1) = nextSegment sabs
(sb1,rb1) = nextSegment base
difSegsFrom :: String -> String -> String
difSegsFrom sabs "" = sabs
difSegsFrom sabs base = difSegsFrom ("../"++sabs) (snd $ nextSegment base)
normalizeCase :: String -> String
normalizeCase uristr = ncScheme uristr
where
ncScheme (':':cs) = ':':ncEscape cs
ncScheme (c:cs) | isSchemeChar c = toLower c:ncScheme cs
ncScheme _ = ncEscape uristr
ncEscape ('%':h1:h2:cs) = '%':toUpper h1:toUpper h2:ncEscape cs
ncEscape (c:cs) = c:ncEscape cs
ncEscape [] = []
normalizeEscape :: String -> String
normalizeEscape ('%':h1:h2:cs)
| isHexDigit h1 && isHexDigit h2 && isUnreserved escval =
escval:normalizeEscape cs
where
escval = chr (digitToInt h1*16+digitToInt h2)
normalizeEscape (c:cs) = c:normalizeEscape cs
normalizeEscape [] = []
normalizePathSegments :: String -> String
normalizePathSegments uristr = normstr juri
where
juri = parseURI uristr
normstr Nothing = uristr
normstr (Just u) = show (normuri u)
normuri u = u { uriPath = removeDotSegments (uriPath u) }
#if __GLASGOW_HASKELL__ >= 800
deriving instance Lift URI
deriving instance Lift URIAuth
#else
instance Lift URI where
lift (URI {..}) = [| URI {..} |]
instance Lift URIAuth where
lift (URIAuth {..}) = [| URIAuth {..} |]
#endif
{-# DEPRECATED parseabsoluteURI "use parseAbsoluteURI" #-}
parseabsoluteURI :: String -> Maybe URI
parseabsoluteURI = parseAbsoluteURI
{-# DEPRECATED escapeString "use escapeURIString, and note the flipped arguments" #-}
escapeString :: String -> (Char->Bool) -> String
escapeString = flip escapeURIString
{-# DEPRECATED reserved "use isReserved" #-}
reserved :: Char -> Bool
reserved = isReserved
{-# DEPRECATED unreserved "use isUnreserved" #-}
unreserved :: Char -> Bool
unreserved = isUnreserved
{-# DEPRECATED scheme "use uriScheme" #-}
scheme :: URI -> String
scheme = orNull init . uriScheme
{-# DEPRECATED authority "use uriAuthority, and note changed functionality" #-}
authority :: URI -> String
authority = dropss . ($"") . uriAuthToString id . uriAuthority
where
dropss ('/':'/':s) = s
dropss s = s
{-# DEPRECATED path "use uriPath" #-}
path :: URI -> String
path = uriPath
{-# DEPRECATED query "use uriQuery, and note changed functionality" #-}
query :: URI -> String
query = orNull tail . uriQuery
{-# DEPRECATED fragment "use uriFragment, and note changed functionality" #-}
fragment :: URI -> String
fragment = orNull tail . uriFragment
orNull :: ([a]->[a]) -> [a] -> [a]
orNull _ [] = []
orNull f as = f as