module Web.Fn (
FnRequest
, defaultFnRequest
, RequestContext(..)
, toWAI
, Req
, route
, fallthrough
, (==>)
, (//)
, (/?)
, path
, end
, anything
, segment
, method
, FromParam(..)
, ParamError(..)
, param
, paramMany
, paramOpt
, File(..)
, file
, files
, staticServe
, okText
, okHtml
, errText
, errHtml
, notFoundText
, notFoundHtml
, redirect
) where
import qualified Blaze.ByteString.Builder.Char.Utf8 as B
import Control.Applicative ((<$>))
import Control.Arrow (second)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy as LB
import Data.Either (rights)
import qualified Data.HashMap.Strict as HM
import Data.Maybe (fromJust)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Data.Text.Read (decimal, double)
import Network.HTTP.Types
import Network.Wai
import Network.Wai.Parse (FileInfo (..), Param,
lbsBackEnd,
parseRequestBody)
import qualified Network.Wai.Parse as Parse
import System.Directory (doesFileExist)
import System.FilePath (takeExtension)
data Store b a = Store b (b -> a)
instance Functor (Store b) where
fmap f (Store b h) = Store b (f . h)
type FnRequest = (Request, ([Param], [Parse.File LB.ByteString]))
defaultFnRequest :: FnRequest
defaultFnRequest = (defaultRequest, ([],[]))
class RequestContext ctxt where
requestLens :: Functor f => (FnRequest -> f FnRequest) -> ctxt -> f ctxt
requestLens f c = setRequest c <$> f (getRequest c)
getRequest :: ctxt -> FnRequest
getRequest c =
let (Store r _) = requestLens (`Store` id) c
in r
setRequest :: ctxt -> FnRequest -> ctxt
setRequest c r =
let (Store _ b) = requestLens (`Store` id) c
in b r
instance RequestContext FnRequest where
getRequest = id
setRequest _ = id
toWAI :: RequestContext ctxt => ctxt -> (ctxt -> IO Response) -> Application
toWAI ctxt f req cont =
do post <- parseRequestBody lbsBackEnd req
let ctxt' = setRequest ctxt (req, post)
f ctxt' >>= cont
route :: RequestContext ctxt =>
ctxt ->
[ctxt -> Req -> Maybe (IO (Maybe Response))] ->
IO (Maybe Response)
route ctxt pths =
do let (r,post) = getRequest ctxt
m = either (const GET) id (parseMethod (requestMethod r))
req = (filter (/= "") (pathInfo r), queryString r, m, post)
route' req pths
where route' _ [] = return Nothing
route' req (x:xs) =
case x ctxt req of
Nothing -> route' req xs
Just action ->
do resp <- action
case resp of
Nothing -> route' req xs
Just response -> return (Just response)
fallthrough :: IO (Maybe Response) -> IO Response -> IO Response
fallthrough a ft =
do response <- a
case response of
Nothing -> ft
Just r -> return r
mimeMap :: HM.HashMap String ByteString
mimeMap = HM.fromList [
( ".asc" , "text/plain" ),
( ".asf" , "video/x-ms-asf" ),
( ".asx" , "video/x-ms-asf" ),
( ".avi" , "video/x-msvideo" ),
( ".bz2" , "application/x-bzip" ),
( ".c" , "text/plain" ),
( ".class" , "application/octet-stream" ),
( ".conf" , "text/plain" ),
( ".cpp" , "text/plain" ),
( ".css" , "text/css" ),
( ".cxx" , "text/plain" ),
( ".dtd" , "text/xml" ),
( ".dvi" , "application/x-dvi" ),
( ".gif" , "image/gif" ),
( ".gz" , "application/x-gzip" ),
( ".hs" , "text/plain" ),
( ".htm" , "text/html" ),
( ".html" , "text/html" ),
( ".ico" , "image/x-icon" ),
( ".jar" , "application/x-java-archive" ),
( ".jpeg" , "image/jpeg" ),
( ".jpg" , "image/jpeg" ),
( ".js" , "text/javascript" ),
( ".json" , "application/json" ),
( ".log" , "text/plain" ),
( ".m3u" , "audio/x-mpegurl" ),
( ".mov" , "video/quicktime" ),
( ".mp3" , "audio/mpeg" ),
( ".mpeg" , "video/mpeg" ),
( ".mpg" , "video/mpeg" ),
( ".ogg" , "application/ogg" ),
( ".pac" , "application/x-ns-proxy-autoconfig" ),
( ".pdf" , "application/pdf" ),
( ".png" , "image/png" ),
( ".ps" , "application/postscript" ),
( ".qt" , "video/quicktime" ),
( ".sig" , "application/pgp-signature" ),
( ".spl" , "application/futuresplash" ),
( ".svg" , "image/svg+xml" ),
( ".swf" , "application/x-shockwave-flash" ),
( ".tar" , "application/x-tar" ),
( ".tar.bz2" , "application/x-bzip-compressed-tar" ),
( ".tar.gz" , "application/x-tgz" ),
( ".tbz" , "application/x-bzip-compressed-tar" ),
( ".text" , "text/plain" ),
( ".tgz" , "application/x-tgz" ),
( ".torrent" , "application/x-bittorrent" ),
( ".ttf" , "application/x-font-truetype" ),
( ".txt" , "text/plain" ),
( ".wav" , "audio/x-wav" ),
( ".wax" , "audio/x-ms-wax" ),
( ".wma" , "audio/x-ms-wma" ),
( ".wmv" , "video/x-ms-wmv" ),
( ".xbm" , "image/x-xbitmap" ),
( ".xml" , "text/xml" ),
( ".xpm" , "image/x-xpixmap" ),
( ".xwd" , "image/x-xwindowdump" ),
( ".zip" , "application/zip" ) ]
staticServe :: RequestContext ctxt => Text -> ctxt -> IO (Maybe Response)
staticServe d ctxt = do
let pth = T.unpack $ T.intercalate "/" $ d : pathInfo (fst . getRequest $ ctxt)
exists <- doesFileExist pth
if exists
then do let ext = takeExtension pth
contentType = case HM.lookup ext mimeMap of
Nothing -> []
Just t -> [(hContentType, t)]
return $ Just $ responseFile status200
contentType
pth
Nothing
else return Nothing
type Req = ([Text], Query, StdMethod, ([Param], [Parse.File LB.ByteString]))
(==>) :: RequestContext ctxt =>
(Req -> Maybe (Req, k -> a)) ->
(ctxt -> k) ->
ctxt ->
Req ->
Maybe a
(match ==> handle) ctxt req =
case match req of
Nothing -> Nothing
Just ((pathInfo',_,_,_), k) ->
let (request, post) = getRequest ctxt in
Just (k $ handle (setRequest ctxt (request { pathInfo = pathInfo' }, post)))
(//) :: (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
findParamMatches :: FromParam p => Text -> [(ByteString, Maybe ByteString)] -> [Either ParamError p]
findParamMatches n ps = map (fromParam . maybe "" T.decodeUtf8 . snd) .
filter ((== T.encodeUtf8 n) . fst) $
ps
param :: FromParam p => Text -> Req -> Maybe (Req, (p -> a) -> a)
param n req =
let (_,q,_,(ps, _)) = req
in case rights $ findParamMatches n q of
[y] -> Just (req, \k -> k y)
[] -> case rights $ findParamMatches n (map (second Just) ps) of
[y] -> Just (req, \k -> k y)
_ -> Nothing
_ -> Nothing
paramMany :: FromParam p => Text -> Req -> Maybe (Req, ([p] -> a) -> a)
paramMany n req =
let (_,q,_,(ps,_)) = req
in case findParamMatches n (q ++ map (second Just) ps) of
[] -> Nothing
xs -> let ys = rights xs in
if length ys == length xs
then Just (req, \k -> k ys)
else Nothing
paramOpt :: FromParam p =>
Text ->
Req ->
Maybe (Req, (Either ParamError [p] -> a) -> a)
paramOpt n req =
let (_,q,_,(ps, _)) = req
in case findParamMatches n (q ++ map (second Just) ps) of
[] -> Just (req, \k -> k (Left ParamMissing))
ys -> Just (req, \k -> k (foldLefts [] ys))
where foldLefts acc [] = Right (reverse acc)
foldLefts _ (Left x : _) = Left x
foldLefts acc (Right x : xs) = foldLefts (x : acc) xs
data File = File { fileName :: Text
, fileContentType :: Text
, fileContent :: LB.ByteString
}
file :: Text -> Req -> Maybe (Req, (File -> a) -> a)
file n req =
let (_,_,_,(_, fs)) = req
in case filter ((== T.encodeUtf8 n) . fst) fs of
[(_, FileInfo nm ct c)] -> Just (req, \k -> k (File (T.decodeUtf8 nm)
(T.decodeUtf8 ct)
c))
_ -> Nothing
files :: Req -> Maybe (Req, ([(Text, File)] -> a) -> a)
files req =
let (_,_,_,(_, fs')) = req
fs = map (\(n, FileInfo nm ct c) ->
(T.decodeUtf8 n, File (T.decodeUtf8 nm)
(T.decodeUtf8 ct)
c))
fs'
in Just (req, \k -> k fs)
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 "")