module Web.Fn (
RequestContext(..)
, toWAI
, Req
, route
, fallthrough
, (==>)
, (//)
, (/?)
, path
, end
, anything
, segment
, method
, FromParam(..)
, ParamError(..)
, param
, paramMany
, paramOpt
, okText
, okHtml
, errText
, errHtml
, notFoundText
, notFoundHtml
, redirect
) where
import qualified Blaze.ByteString.Builder.Char.Utf8 as B
import Data.ByteString (ByteString)
import Data.Either (rights)
import Data.Maybe (fromJust)
import Data.Text (Text)
import qualified Data.Text.Encoding as T
import Data.Text.Read (decimal, double)
import Network.HTTP.Types
import Network.Wai
import Network.Wai.Parse (File, Param)
data Store b a = Store b (b -> a)
instance Functor (Store b) where
fmap f (Store b h) = Store b (f . h)
class RequestContext ctxt where
requestLens :: Functor f => (Request -> f Request) -> ctxt -> f ctxt
requestLens f c = setRequest c <$> f (getRequest c)
getRequest :: ctxt -> Request
getRequest c =
let (Store r _) = requestLens (`Store` id) c
in r
setRequest :: ctxt -> Request -> ctxt
setRequest c r =
let (Store _ b) = requestLens (`Store` id) c
in b r
toWAI :: RequestContext ctxt => ctxt -> (ctxt -> IO Response) -> Application
toWAI ctxt f req cont = let ctxt' = setRequest ctxt req
in f ctxt' >>= cont
fallthrough :: IO (Maybe Response) -> IO Response -> IO Response
fallthrough a ft =
do response <- a
case response of
Nothing -> ft
Just r -> return r
route :: RequestContext ctxt =>
ctxt ->
[ctxt -> Maybe (IO (Maybe Response))] ->
IO (Maybe Response)
route _ [] = return Nothing
route ctxt (x:xs) =
case x ctxt of
Nothing -> route ctxt xs
Just action ->
do resp <- action
case resp of
Nothing -> route ctxt xs
Just response -> return (Just response)
type Req = ([Text], Query, StdMethod, Maybe ([Param], [File ByteString]))
(==>) :: RequestContext ctxt =>
(Req -> Maybe (Req, k -> a)) ->
(ctxt -> k) ->
ctxt ->
Maybe a
(match ==> handle) ctxt =
let r = getRequest ctxt
m = either (const GET) id (parseMethod (requestMethod r))
x = (pathInfo r, queryString r, m, Nothing)
in case match x of
Nothing -> Nothing
Just ((pathInfo',_,_,_), k) -> Just (k $ handle (setRequest ctxt ((getRequest ctxt) { pathInfo = pathInfo' })))
(//) :: (r -> Maybe (r, k -> k')) ->
(r -> Maybe (r, k' -> a)) ->
r -> Maybe (r, k -> a)
(match1 // match2) req =
case match1 req of
Nothing -> Nothing
Just (req', k) -> case match2 req' of
Nothing -> Nothing
Just (req'', k') -> Just (req'', k' . k)
(/?) :: (r -> Maybe (r, k -> k')) ->
(r -> Maybe (r, k' -> a)) ->
r -> Maybe (r, k -> a)
(/?) = (//)
path :: Text -> Req -> Maybe (Req, a -> a)
path s req =
case req of
(y:ys,q,m,x) | y == s -> Just ((ys, q, m, x), id)
_ -> Nothing
end :: Req -> Maybe (Req, a -> a)
end req =
case req of
([],_,_,_) -> Just (req, id)
_ -> Nothing
anything :: Req -> Maybe (Req, a -> a)
anything req = Just (req, id)
segment :: FromParam p => Req -> Maybe (Req, (p -> a) -> a)
segment req =
case req of
(y:ys,q,m,x) -> case fromParam y of
Left _ -> Nothing
Right p -> Just ((ys, q, m, x), \k -> k p)
_ -> Nothing
method :: StdMethod -> Req -> Maybe (Req, a -> a)
method m r@(_,_,m',_) | m == m' = Just (r, id)
method _ _ = Nothing
data ParamError = ParamMissing | ParamUnparsable | ParamOtherError Text deriving (Eq, Show)
class FromParam a where
fromParam :: Text -> Either ParamError a
instance FromParam Text where
fromParam = Right
instance FromParam Int where
fromParam t = case decimal t of
Left _ -> Left ParamUnparsable
Right m | snd m /= "" ->
Left ParamUnparsable
Right (v, _) -> Right v
instance FromParam Double where
fromParam t = case double t of
Left _ -> Left ParamUnparsable
Right m | snd m /= "" ->
Left ParamUnparsable
Right (v, _) -> Right v
param :: FromParam p => Text -> Req -> Maybe (Req, (p -> a) -> a)
param n req =
let (_,q,_,_) = req
match = filter ((== T.encodeUtf8 n) . fst) q
in case rights (map (fromParam . maybe "" T.decodeUtf8 . snd) match) of
[x] -> Just (req, \k -> k x)
_ -> Nothing
paramMany :: FromParam p => Text -> Req -> Maybe (Req, ([p] -> a) -> a)
paramMany n req =
let (_,q,_,_) = req
match = filter ((== T.encodeUtf8 n) . fst) q
in case map (maybe "" T.decodeUtf8 . snd) match of
[] -> Nothing
xs -> let ps = rights $ map fromParam xs in
if length ps == length xs
then Just (req, \k -> k ps)
else Nothing
paramOpt :: FromParam p =>
Text ->
Req ->
Maybe (Req, (Either ParamError [p] -> a) -> a)
paramOpt n req =
let (_,q,_,_) = req
match = filter ((== T.encodeUtf8 n) . fst) q
in case map (maybe "" T.decodeUtf8 . snd) match of
[] -> Just (req, \k -> k (Left ParamMissing))
ps -> Just (req, \k -> k (foldLefts [] (map fromParam ps)))
where foldLefts acc [] = Right (reverse acc)
foldLefts _ (Left x : _) = Left x
foldLefts acc (Right x : xs) = foldLefts (x : acc) xs
returnText :: Text -> Status -> ByteString -> IO (Maybe Response)
returnText text status content =
return $ Just $
responseBuilder status
[(hContentType, content)]
(B.fromText text)
plainText :: ByteString
plainText = "text/plain; charset=utf-8"
html :: ByteString
html = "text/html; charset=utf-8"
okText :: Text -> IO (Maybe Response)
okText t = returnText t status200 plainText
okHtml :: Text -> IO (Maybe Response)
okHtml t = returnText t status200 html
errText :: Text -> IO (Maybe Response)
errText t = returnText t status500 plainText
errHtml :: Text -> IO (Maybe Response)
errHtml t = returnText t status500 html
notFoundText :: Text -> IO Response
notFoundText t = fromJust <$> returnText t status404 plainText
notFoundHtml :: Text -> IO Response
notFoundHtml t = fromJust <$> returnText t status404 html
redirect :: Text -> IO (Maybe Response)
redirect target =
return $ Just $
responseBuilder status303
[(hLocation, T.encodeUtf8 target)]
(B.fromText "")