{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Network.Wai.UrlMap (
UrlMap',
UrlMap,
mount',
mount,
mountRoot,
mapUrls,
) where
import Control.Applicative
import qualified Data.ByteString as B
import Data.List (stripPrefix)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Network.HTTP.Types (hContentType, status404)
import Network.Wai (Application, Request (pathInfo, rawPathInfo), responseLBS)
type Path = [Text]
newtype UrlMap' a = UrlMap' { forall a. UrlMap' a -> [(Path, a)]
unUrlMap :: [(Path, a)] }
instance Functor UrlMap' where
fmap :: forall a b. (a -> b) -> UrlMap' a -> UrlMap' b
fmap a -> b
f (UrlMap' [(Path, a)]
xs) = forall a. [(Path, a)] -> UrlMap' a
UrlMap' (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Path
p, a
a) -> (Path
p, a -> b
f a
a)) [(Path, a)]
xs)
instance Applicative UrlMap' where
pure :: forall a. a -> UrlMap' a
pure a
x = forall a. [(Path, a)] -> UrlMap' a
UrlMap' [([], a
x)]
(UrlMap' [(Path, a -> b)]
xs) <*> :: forall a b. UrlMap' (a -> b) -> UrlMap' a -> UrlMap' b
<*> (UrlMap' [(Path, a)]
ys) = forall a. [(Path, a)] -> UrlMap' a
UrlMap' [ (Path
p, a -> b
f a
y) |
(Path
p, a
y) <- [(Path, a)]
ys,
a -> b
f <- forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd [(Path, a -> b)]
xs ]
instance Alternative UrlMap' where
empty :: forall a. UrlMap' a
empty = forall a. [(Path, a)] -> UrlMap' a
UrlMap' forall (f :: * -> *) a. Alternative f => f a
empty
(UrlMap' [(Path, a)]
xs) <|> :: forall a. UrlMap' a -> UrlMap' a -> UrlMap' a
<|> (UrlMap' [(Path, a)]
ys) = forall a. [(Path, a)] -> UrlMap' a
UrlMap' ([(Path, a)]
xs forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [(Path, a)]
ys)
type UrlMap = UrlMap' Application
mount' :: ToApplication a => Path -> a -> UrlMap
mount' :: forall a. ToApplication a => Path -> a -> UrlMap
mount' Path
prefix a
thing = forall a. [(Path, a)] -> UrlMap' a
UrlMap' [(Path
prefix, forall a. ToApplication a => a -> Application
toApplication a
thing)]
mount :: ToApplication a => Text -> a -> UrlMap
mount :: forall a. ToApplication a => Text -> a -> UrlMap
mount Text
prefix a
thing = forall a. ToApplication a => Path -> a -> UrlMap
mount' [Text
prefix] a
thing
mountRoot :: ToApplication a => a -> UrlMap
mountRoot :: forall a. ToApplication a => a -> UrlMap
mountRoot = forall a. ToApplication a => Path -> a -> UrlMap
mount' []
try :: Eq a
=> [a]
-> [([a], b)]
-> Maybe ([a], b)
try :: forall a b. Eq a => [a] -> [([a], b)] -> Maybe ([a], b)
try [a]
xs [([a], b)]
tuples = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl forall {b}. Maybe ([a], b) -> ([a], b) -> Maybe ([a], b)
go forall a. Maybe a
Nothing [([a], b)]
tuples
where
go :: Maybe ([a], b) -> ([a], b) -> Maybe ([a], b)
go (Just ([a], b)
x) ([a], b)
_ = forall a. a -> Maybe a
Just ([a], b)
x
go Maybe ([a], b)
_ ([a]
prefix, b
y) = forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix [a]
prefix [a]
xs forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[a]
xs' -> forall (m :: * -> *) a. Monad m => a -> m a
return ([a]
xs', b
y)
class ToApplication a where
toApplication :: a -> Application
instance ToApplication Application where
toApplication :: Application -> Application
toApplication = forall a. a -> a
id
instance ToApplication UrlMap where
toApplication :: UrlMap -> Application
toApplication UrlMap
urlMap Request
req Response -> IO ResponseReceived
sendResponse =
case forall a b. Eq a => [a] -> [([a], b)] -> Maybe ([a], b)
try (Request -> Path
pathInfo Request
req) (forall a. UrlMap' a -> [(Path, a)]
unUrlMap UrlMap
urlMap) of
Just (Path
newPath, Application
app) ->
Application
app (Request
req { pathInfo :: Path
pathInfo = Path
newPath
, rawPathInfo :: ByteString
rawPathInfo = Path -> ByteString
makeRaw Path
newPath
}) Response -> IO ResponseReceived
sendResponse
Maybe (Path, Application)
Nothing ->
Response -> IO ResponseReceived
sendResponse forall a b. (a -> b) -> a -> b
$ Status -> ResponseHeaders -> ByteString -> Response
responseLBS
Status
status404
[(HeaderName
hContentType, ByteString
"text/plain")]
ByteString
"Not found\n"
where
makeRaw :: [Text] -> B.ByteString
makeRaw :: Path -> ByteString
makeRaw = (ByteString
"/" ByteString -> ByteString -> ByteString
`B.append`) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
T.encodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Path -> Text
T.intercalate Text
"/"
mapUrls :: UrlMap -> Application
mapUrls :: UrlMap -> Application
mapUrls = forall a. ToApplication a => a -> Application
toApplication