module Web.Scotty.Action
( addHeader
, body
, file
, files
, header
, headers
, html
, json
, jsonData
, next
, param
, params
, raise
, raw
, readEither
, redirect
, request
, rescue
, setHeader
, status
, stream
, source
, text
, Param
, Parsable(..)
, runAction
) where
import Blaze.ByteString.Builder (Builder, fromLazyByteString)
#if MIN_VERSION_mtl(2,2,1)
import Control.Monad.Except
#else
import Control.Monad.Error
#endif
import Control.Monad.Reader
import qualified Control.Monad.State as MS
import qualified Data.Aeson as A
import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Lazy.Char8 as BL
import qualified Data.CaseInsensitive as CI
import Data.Conduit
import qualified Data.Conduit.List as CL
import Data.Default (def)
import Data.Monoid (mconcat)
import qualified Data.Text as ST
import qualified Data.Text.Lazy as T
import Data.Text.Lazy.Encoding (encodeUtf8)
import Network.HTTP.Types
import Network.Wai
import Web.Scotty.Internal.Types
import Web.Scotty.Util
runAction :: (ScottyError e, Monad m) => ErrorHandler e m -> ActionEnv -> ActionT e m () -> m (Maybe Response)
runAction h env action = do
(e,r) <- flip MS.runStateT def
$ flip runReaderT env
#if MIN_VERSION_mtl(2,2,1)
$ runExceptT
#else
$ runErrorT
#endif
$ runAM
$ action `catchError` (defH h)
return $ either (const Nothing) (const $ Just $ mkResponse r) e
defH :: (ScottyError e, Monad m) => ErrorHandler e m -> ActionError e -> ActionT e m ()
defH _ (Redirect url) = do
status status302
setHeader "Location" url
defH Nothing (ActionError e) = do
status status500
html $ mconcat ["<h1>500 Internal Server Error</h1>", showError e]
defH h@(Just f) (ActionError e) = f e `catchError` (defH h)
defH _ Next = next
raise :: (ScottyError e, Monad m) => e -> ActionT e m a
raise = throwError . ActionError
next :: (ScottyError e, Monad m) => ActionT e m a
next = throwError Next
rescue :: (ScottyError e, Monad m) => ActionT e m a -> (e -> ActionT e m a) -> ActionT e m a
rescue action h = catchError action $ \e -> case e of
ActionError err -> h err
other -> throwError other
redirect :: (ScottyError e, Monad m) => T.Text -> ActionT e m a
redirect = throwError . Redirect
request :: (ScottyError e, Monad m) => ActionT e m Request
request = ActionT $ liftM getReq ask
files :: (ScottyError e, Monad m) => ActionT e m [File]
files = ActionT $ liftM getFiles ask
header :: (ScottyError e, Monad m) => T.Text -> ActionT e m (Maybe T.Text)
header k = do
hs <- liftM requestHeaders request
return $ fmap strictByteStringToLazyText $ lookup (CI.mk (lazyTextToStrictByteString k)) hs
headers :: (ScottyError e, Monad m) => ActionT e m [(T.Text, T.Text)]
headers = do
hs <- liftM requestHeaders request
return [ ( strictByteStringToLazyText (CI.original k)
, strictByteStringToLazyText v)
| (k,v) <- hs ]
body :: (ScottyError e, Monad m) => ActionT e m BL.ByteString
body = ActionT $ liftM getBody ask
jsonData :: (A.FromJSON a, ScottyError e, Monad m) => ActionT e m a
jsonData = do
b <- body
maybe (raise $ stringError $ "jsonData - no parse: " ++ BL.unpack b) return $ A.decode b
param :: (Parsable a, ScottyError e, Monad m) => T.Text -> ActionT e m a
param k = do
val <- ActionT $ liftM (lookup k . getParams) ask
case val of
Nothing -> raise $ stringError $ "Param: " ++ T.unpack k ++ " not found!"
Just v -> either (const next) return $ parseParam v
params :: (ScottyError e, Monad m) => ActionT e m [Param]
params = ActionT $ liftM getParams ask
class Parsable a where
parseParam :: T.Text -> Either T.Text a
parseParamList :: T.Text -> Either T.Text [a]
parseParamList t = mapM parseParam (T.split (== ',') t)
instance Parsable T.Text where parseParam = Right
instance Parsable ST.Text where parseParam = Right . T.toStrict
instance Parsable B.ByteString where parseParam = Right . lazyTextToStrictByteString
instance Parsable Char where
parseParam t = case T.unpack t of
[c] -> Right c
_ -> Left "parseParam Char: no parse"
parseParamList = Right . T.unpack
instance Parsable () where
parseParam t = if T.null t then Right () else Left "parseParam Unit: no parse"
instance (Parsable a) => Parsable [a] where parseParam = parseParamList
instance Parsable Bool where
parseParam t = if t' == T.toCaseFold "true"
then Right True
else if t' == T.toCaseFold "false"
then Right False
else Left "parseParam Bool: no parse"
where t' = T.toCaseFold t
instance Parsable Double where parseParam = readEither
instance Parsable Float where parseParam = readEither
instance Parsable Int where parseParam = readEither
instance Parsable Integer where parseParam = readEither
readEither :: (Read a) => T.Text -> Either T.Text a
readEither t = case [ x | (x,"") <- reads (T.unpack t) ] of
[x] -> Right x
[] -> Left "readEither: no parse"
_ -> Left "readEither: ambiguous parse"
status :: (ScottyError e, Monad m) => Status -> ActionT e m ()
status = ActionT . MS.modify . setStatus
addHeader :: (ScottyError e, Monad m) => T.Text -> T.Text -> ActionT e m ()
addHeader k v = ActionT . MS.modify $ setHeaderWith $ add (CI.mk $ lazyTextToStrictByteString k) (lazyTextToStrictByteString v)
setHeader :: (ScottyError e, Monad m) => T.Text -> T.Text -> ActionT e m ()
setHeader k v = ActionT . MS.modify $ setHeaderWith $ replace (CI.mk $ lazyTextToStrictByteString k) (lazyTextToStrictByteString v)
text :: (ScottyError e, Monad m) => T.Text -> ActionT e m ()
text t = do
setHeader "Content-Type" "text/plain"
raw $ encodeUtf8 t
html :: (ScottyError e, Monad m) => T.Text -> ActionT e m ()
html t = do
setHeader "Content-Type" "text/html"
raw $ encodeUtf8 t
file :: (ScottyError e, Monad m) => FilePath -> ActionT e m ()
file = ActionT . MS.modify . setContent . ContentFile
json :: (A.ToJSON a, ScottyError e, Monad m) => a -> ActionT e m ()
json v = do
setHeader "Content-Type" "application/json"
raw $ A.encode v
stream :: (ScottyError e, Monad m) => StreamingBody -> ActionT e m ()
stream = ActionT . MS.modify . setContent . ContentStream
source :: (ScottyError e, Monad m) => Source IO (Flush Builder) -> ActionT e m ()
source src = stream $ \send flush -> src $$ CL.mapM_ (\mbuilder ->
case mbuilder of
Chunk b -> send b
Flush -> flush)
raw :: (ScottyError e, Monad m) => BL.ByteString -> ActionT e m ()
raw = ActionT . MS.modify . setContent . ContentBuilder . fromLazyByteString