{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, TypeSynonymInstances #-}
module Happstack.Server.SURI
( path
, query
, scheme
, u_scheme
, u_path
, a_scheme
, a_path
, percentDecode
, unEscape
, unEscapeQS
, isAbs
, SURI(..)
, render
, parse
, ToSURI(..)
, FromPath(..)
)
where
import Control.Arrow (first)
import Data.Char (chr, digitToInt, isHexDigit)
import Data.Maybe (fromJust, isJust)
import Data.Generics (Data, Typeable)
import qualified Data.Text as Text
import qualified Data.Text.Lazy as LazyText
import qualified Network.URI as URI
path :: SURI -> String
path = URI.uriPath . suri
query :: SURI -> String
query = URI.uriQuery . suri
scheme :: SURI -> String
scheme = URI.uriScheme . suri
u_scheme :: (String -> String) -> SURI -> SURI
u_scheme f (SURI u) = SURI (u {URI.uriScheme=f $ URI.uriScheme u})
u_path :: (String -> String) -> SURI -> SURI
u_path f (SURI u) = SURI $ u {URI.uriPath=f $ URI.uriPath u}
a_scheme :: String -> SURI -> SURI
a_scheme a (SURI u) = SURI $ u {URI.uriScheme=a}
a_path :: String -> SURI -> SURI
a_path a (SURI u) = SURI $ u {URI.uriPath=a}
percentDecode :: String -> String
percentDecode [] = ""
percentDecode ('%':x1:x2:s) | isHexDigit x1 && isHexDigit x2 =
chr (digitToInt x1 * 16 + digitToInt x2) : percentDecode s
percentDecode (c:s) = c : percentDecode s
unEscape, unEscapeQS :: String -> String
unEscapeQS = percentDecode . map (\x->if x=='+' then ' ' else x)
unEscape = percentDecode
isAbs :: SURI -> Bool
isAbs = not . null . URI.uriScheme . suri
newtype SURI = SURI {suri::URI.URI} deriving (Eq,Data,Typeable)
instance Show SURI where
showsPrec d (SURI uri) = showsPrec d $ show uri
instance Read SURI where
readsPrec d = mapFst fromJust . filter (isJust . fst) . mapFst parse . readsPrec d
where
mapFst :: (a -> b) -> [(a,x)] -> [(b,x)]
mapFst = map . first
instance Ord SURI where
compare a b = show a `compare` show b
render :: (ToSURI a) => a -> String
render = show . suri . toSURI
parse :: String -> Maybe SURI
parse = fmap SURI . URI.parseURIReference
class ToSURI x where toSURI::x->SURI
instance ToSURI SURI where toSURI=id
instance ToSURI URI.URI where toSURI=SURI
instance ToSURI String where
toSURI = maybe (SURI $ URI.URI "" Nothing "" "" "") id . parse
instance ToSURI Text.Text where toSURI = toSURI . Text.unpack
instance ToSURI LazyText.Text where toSURI = toSURI . LazyText.unpack
class FromPath x where fromPath::String->x