{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
module Web.Scotty.Action
( addHeader
, body
, bodyReader
, file
, files
, finish
, header
, headers
, html
, liftAndCatchIO
, json
, jsonData
, next
, param
, params
, raise
, raiseStatus
, raw
, readEither
, redirect
, request
, rescue
, setHeader
, status
, stream
, text
, Param
, Parsable(..)
, runAction
) where
import Blaze.ByteString.Builder (fromLazyByteString)
import qualified Control.Exception as E
import Control.Monad.Error.Class
import Control.Monad.Reader hiding (mapM)
import qualified Control.Monad.State.Strict as MS
import Control.Monad.Trans.Except
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.Default.Class (def)
import Data.Int
import qualified Data.Text as ST
import qualified Data.Text.Encoding as STE
import qualified Data.Text.Lazy as T
import Data.Text.Lazy.Encoding (encodeUtf8)
import Data.Word
import Network.HTTP.Types
#if !MIN_VERSION_http_types(0,11,0)
import Network.HTTP.Types.Status
#endif
import Network.Wai
import Numeric.Natural
import Prelude ()
import Prelude.Compat
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
$ runExceptT
$ 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 s e) = do
status s
let code = T.pack $ show $ statusCode s
let msg = T.fromStrict $ STE.decodeUtf8 $ statusMessage s
html $ mconcat ["<h1>", code, " ", msg, "</h1>", showError e]
defH h@(Just f) (ActionError _ e) = f e `catchError` (defH h)
defH _ Next = next
defH _ Finish = return ()
raise :: (ScottyError e, Monad m) => e -> ActionT e m a
raise = raiseStatus status500
raiseStatus :: (ScottyError e, Monad m) => Status -> e -> ActionT e m a
raiseStatus s = throwError . ActionError s
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
liftAndCatchIO :: (ScottyError e, MonadIO m) => IO a -> ActionT e m a
liftAndCatchIO io = ActionT $ do
r <- liftIO $ liftM Right io `E.catch` (\ e -> return $ Left $ stringError $ show (e :: E.SomeException))
either throwError return r
redirect :: (ScottyError e, Monad m) => T.Text -> ActionT e m a
redirect = throwError . Redirect
finish :: (ScottyError e, Monad m) => ActionT e m a
finish = throwError Finish
request :: Monad m => ActionT e m Request
request = ActionT $ liftM getReq ask
files :: 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, MonadIO m) => ActionT e m BL.ByteString
body = ActionT ask >>= (liftIO . getBody)
bodyReader :: Monad m => ActionT e m (IO B.ByteString)
bodyReader = ActionT $ getBodyChunk `liftM` ask
jsonData :: (A.FromJSON a, ScottyError e, MonadIO m) => ActionT e m a
jsonData = do
b <- body
when (b == "") $ do
let htmlError = "jsonData - No data was provided."
raiseStatus status400 $ stringError htmlError
case A.eitherDecode b of
Left err -> do
let htmlError = "jsonData - malformed."
`mappend` " Data was: " `mappend` BL.unpack b
`mappend` " Error was: " `mappend` err
raiseStatus status400 $ stringError htmlError
Right value -> case A.fromJSON value of
A.Error err -> do
let htmlError = "jsonData - failed parse."
`mappend` " Data was: " `mappend` BL.unpack b `mappend` "."
`mappend` " Error was: " `mappend` err
raiseStatus status422 $ stringError htmlError
A.Success a -> do
return a
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 :: 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 BL.ByteString where parseParam = Right . encodeUtf8
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 Int8 where parseParam = readEither
instance Parsable Int16 where parseParam = readEither
instance Parsable Int32 where parseParam = readEither
instance Parsable Int64 where parseParam = readEither
instance Parsable Integer where parseParam = readEither
instance Parsable Word where parseParam = readEither
instance Parsable Word8 where parseParam = readEither
instance Parsable Word16 where parseParam = readEither
instance Parsable Word32 where parseParam = readEither
instance Parsable Word64 where parseParam = readEither
instance Parsable Natural 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 :: Monad m => Status -> ActionT e m ()
status = ActionT . MS.modify . setStatus
changeHeader :: Monad m
=> (CI.CI B.ByteString -> B.ByteString -> [(HeaderName, B.ByteString)] -> [(HeaderName, B.ByteString)])
-> T.Text -> T.Text -> ActionT e m ()
changeHeader f k = ActionT
. MS.modify
. setHeaderWith
. f (CI.mk $ lazyTextToStrictByteString k)
. lazyTextToStrictByteString
addHeader :: Monad m => T.Text -> T.Text -> ActionT e m ()
addHeader = changeHeader add
setHeader :: Monad m => T.Text -> T.Text -> ActionT e m ()
setHeader = changeHeader replace
text :: (ScottyError e, Monad m) => T.Text -> ActionT e m ()
text t = do
changeHeader addIfNotPresent "Content-Type" "text/plain; charset=utf-8"
raw $ encodeUtf8 t
html :: (ScottyError e, Monad m) => T.Text -> ActionT e m ()
html t = do
changeHeader addIfNotPresent "Content-Type" "text/html; charset=utf-8"
raw $ encodeUtf8 t
file :: 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
changeHeader addIfNotPresent "Content-Type" "application/json; charset=utf-8"
raw $ A.encode v
stream :: Monad m => StreamingBody -> ActionT e m ()
stream = ActionT . MS.modify . setContent . ContentStream
raw :: Monad m => BL.ByteString -> ActionT e m ()
raw = ActionT . MS.modify . setContent . ContentBuilder . fromLazyByteString