{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE RecordWildCards #-}
module Web.Scotty.Internal.Types where
import Blaze.ByteString.Builder (Builder)
import Control.Applicative
import Control.Exception (Exception)
import qualified Control.Exception as E
import qualified Control.Monad as Monad
import Control.Monad (MonadPlus(..))
import Control.Monad.Base (MonadBase, liftBase, liftBaseDefault)
import Control.Monad.Catch (MonadCatch, catch, MonadThrow, throwM)
import Control.Monad.Error.Class
import qualified Control.Monad.Fail as Fail
import Control.Monad.IO.Class (MonadIO)
import Control.Monad.Reader (MonadReader(..), ReaderT, mapReaderT)
import Control.Monad.State.Strict (MonadState(..), State, StateT, mapStateT)
import Control.Monad.Trans.Class (MonadTrans(..))
import Control.Monad.Trans.Control (MonadBaseControl, StM, liftBaseWith, restoreM, ComposeSt, defaultLiftBaseWith, defaultRestoreM, MonadTransControl, StT, liftWith, restoreT)
import Control.Monad.Trans.Except
import qualified Data.ByteString as BS
import Data.ByteString.Lazy.Char8 (ByteString)
import Data.Default.Class (Default, def)
import Data.String (IsString(..))
import Data.Text.Lazy (Text, pack)
import Data.Typeable (Typeable)
import Network.HTTP.Types
import Network.Wai hiding (Middleware, Application)
import qualified Network.Wai as Wai
import Network.Wai.Handler.Warp (Settings, defaultSettings)
import Network.Wai.Parse (FileInfo)
import Prelude ()
import Prelude.Compat
data Options = Options { Options -> Int
verbose :: Int
, Options -> Settings
settings :: Settings
}
instance Default Options where
def :: Options
def = Int -> Settings -> Options
Options Int
1 Settings
defaultSettings
newtype RouteOptions = RouteOptions { RouteOptions -> Maybe Int
maxRequestBodySize :: Maybe Kilobytes
}
instance Default RouteOptions where
def :: RouteOptions
def = Maybe Int -> RouteOptions
RouteOptions forall a. Maybe a
Nothing
type Kilobytes = Int
type Middleware m = Application m -> Application m
type Application m = Request -> m Response
data ScottyState e m =
ScottyState { forall e (m :: * -> *). ScottyState e m -> [Middleware]
middlewares :: [Wai.Middleware]
, forall e (m :: * -> *). ScottyState e m -> [Middleware m]
routes :: [Middleware m]
, forall e (m :: * -> *). ScottyState e m -> ErrorHandler e m
handler :: ErrorHandler e m
, forall e (m :: * -> *). ScottyState e m -> RouteOptions
routeOptions :: RouteOptions
}
instance Default (ScottyState e m) where
def :: ScottyState e m
def = forall e (m :: * -> *).
[Middleware]
-> [Middleware m]
-> ErrorHandler e m
-> RouteOptions
-> ScottyState e m
ScottyState [] [] forall a. Maybe a
Nothing forall a. Default a => a
def
addMiddleware :: Wai.Middleware -> ScottyState e m -> ScottyState e m
addMiddleware :: forall e (m :: * -> *).
Middleware -> ScottyState e m -> ScottyState e m
addMiddleware Middleware
m s :: ScottyState e m
s@(ScottyState {middlewares :: forall e (m :: * -> *). ScottyState e m -> [Middleware]
middlewares = [Middleware]
ms}) = ScottyState e m
s { middlewares :: [Middleware]
middlewares = Middleware
mforall a. a -> [a] -> [a]
:[Middleware]
ms }
addRoute :: Middleware m -> ScottyState e m -> ScottyState e m
addRoute :: forall (m :: * -> *) e.
Middleware m -> ScottyState e m -> ScottyState e m
addRoute Middleware m
r s :: ScottyState e m
s@(ScottyState {routes :: forall e (m :: * -> *). ScottyState e m -> [Middleware m]
routes = [Middleware m]
rs}) = ScottyState e m
s { routes :: [Middleware m]
routes = Middleware m
rforall a. a -> [a] -> [a]
:[Middleware m]
rs }
addHandler :: ErrorHandler e m -> ScottyState e m -> ScottyState e m
addHandler :: forall e (m :: * -> *).
ErrorHandler e m -> ScottyState e m -> ScottyState e m
addHandler ErrorHandler e m
h ScottyState e m
s = ScottyState e m
s { handler :: ErrorHandler e m
handler = ErrorHandler e m
h }
updateMaxRequestBodySize :: RouteOptions -> ScottyState e m -> ScottyState e m
updateMaxRequestBodySize :: forall e (m :: * -> *).
RouteOptions -> ScottyState e m -> ScottyState e m
updateMaxRequestBodySize RouteOptions { Maybe Int
maxRequestBodySize :: Maybe Int
maxRequestBodySize :: RouteOptions -> Maybe Int
.. } s :: ScottyState e m
s@ScottyState { routeOptions :: forall e (m :: * -> *). ScottyState e m -> RouteOptions
routeOptions = RouteOptions
ro } =
let ro' :: RouteOptions
ro' = RouteOptions
ro { maxRequestBodySize :: Maybe Int
maxRequestBodySize = Maybe Int
maxRequestBodySize }
in ScottyState e m
s { routeOptions :: RouteOptions
routeOptions = RouteOptions
ro' }
newtype ScottyT e m a = ScottyT { forall e (m :: * -> *) a.
ScottyT e m a -> State (ScottyState e m) a
runS :: State (ScottyState e m) a }
deriving ( forall a b. a -> ScottyT e m b -> ScottyT e m a
forall a b. (a -> b) -> ScottyT e m a -> ScottyT e m b
forall e (m :: * -> *) a b. a -> ScottyT e m b -> ScottyT e m a
forall e (m :: * -> *) a b.
(a -> b) -> ScottyT e m a -> ScottyT e m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> ScottyT e m b -> ScottyT e m a
$c<$ :: forall e (m :: * -> *) a b. a -> ScottyT e m b -> ScottyT e m a
fmap :: forall a b. (a -> b) -> ScottyT e m a -> ScottyT e m b
$cfmap :: forall e (m :: * -> *) a b.
(a -> b) -> ScottyT e m a -> ScottyT e m b
Functor, forall a. a -> ScottyT e m a
forall a b. ScottyT e m a -> ScottyT e m b -> ScottyT e m a
forall a b. ScottyT e m a -> ScottyT e m b -> ScottyT e m b
forall a b. ScottyT e m (a -> b) -> ScottyT e m a -> ScottyT e m b
forall a b c.
(a -> b -> c) -> ScottyT e m a -> ScottyT e m b -> ScottyT e m c
forall e (m :: * -> *). Functor (ScottyT e m)
forall e (m :: * -> *) a. a -> ScottyT e m a
forall e (m :: * -> *) a b.
ScottyT e m a -> ScottyT e m b -> ScottyT e m a
forall e (m :: * -> *) a b.
ScottyT e m a -> ScottyT e m b -> ScottyT e m b
forall e (m :: * -> *) a b.
ScottyT e m (a -> b) -> ScottyT e m a -> ScottyT e m b
forall e (m :: * -> *) a b c.
(a -> b -> c) -> ScottyT e m a -> ScottyT e m b -> ScottyT e m c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: forall a b. ScottyT e m a -> ScottyT e m b -> ScottyT e m a
$c<* :: forall e (m :: * -> *) a b.
ScottyT e m a -> ScottyT e m b -> ScottyT e m a
*> :: forall a b. ScottyT e m a -> ScottyT e m b -> ScottyT e m b
$c*> :: forall e (m :: * -> *) a b.
ScottyT e m a -> ScottyT e m b -> ScottyT e m b
liftA2 :: forall a b c.
(a -> b -> c) -> ScottyT e m a -> ScottyT e m b -> ScottyT e m c
$cliftA2 :: forall e (m :: * -> *) a b c.
(a -> b -> c) -> ScottyT e m a -> ScottyT e m b -> ScottyT e m c
<*> :: forall a b. ScottyT e m (a -> b) -> ScottyT e m a -> ScottyT e m b
$c<*> :: forall e (m :: * -> *) a b.
ScottyT e m (a -> b) -> ScottyT e m a -> ScottyT e m b
pure :: forall a. a -> ScottyT e m a
$cpure :: forall e (m :: * -> *) a. a -> ScottyT e m a
Applicative, forall a. a -> ScottyT e m a
forall a b. ScottyT e m a -> ScottyT e m b -> ScottyT e m b
forall a b. ScottyT e m a -> (a -> ScottyT e m b) -> ScottyT e m b
forall e (m :: * -> *). Applicative (ScottyT e m)
forall e (m :: * -> *) a. a -> ScottyT e m a
forall e (m :: * -> *) a b.
ScottyT e m a -> ScottyT e m b -> ScottyT e m b
forall e (m :: * -> *) a b.
ScottyT e m a -> (a -> ScottyT e m b) -> ScottyT e m b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: forall a. a -> ScottyT e m a
$creturn :: forall e (m :: * -> *) a. a -> ScottyT e m a
>> :: forall a b. ScottyT e m a -> ScottyT e m b -> ScottyT e m b
$c>> :: forall e (m :: * -> *) a b.
ScottyT e m a -> ScottyT e m b -> ScottyT e m b
>>= :: forall a b. ScottyT e m a -> (a -> ScottyT e m b) -> ScottyT e m b
$c>>= :: forall e (m :: * -> *) a b.
ScottyT e m a -> (a -> ScottyT e m b) -> ScottyT e m b
Monad )
data ActionError e
= Redirect Text
| Next
| Finish
| ActionError Status e
class ScottyError e where
stringError :: String -> e
showError :: e -> Text
instance ScottyError Text where
stringError :: String -> Text
stringError = String -> Text
pack
showError :: Text -> Text
showError = forall a. a -> a
id
instance ScottyError e => ScottyError (ActionError e) where
stringError :: String -> ActionError e
stringError = forall e. Status -> e -> ActionError e
ActionError Status
status500 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e. ScottyError e => String -> e
stringError
showError :: ActionError e -> Text
showError (Redirect Text
url) = Text
url
showError ActionError e
Next = String -> Text
pack String
"Next"
showError ActionError e
Finish = String -> Text
pack String
"Finish"
showError (ActionError Status
_ e
e) = forall e. ScottyError e => e -> Text
showError e
e
type ErrorHandler e m = Maybe (e -> ActionT e m ())
data ScottyException = RequestException BS.ByteString Status deriving (Int -> ScottyException -> ShowS
[ScottyException] -> ShowS
ScottyException -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScottyException] -> ShowS
$cshowList :: [ScottyException] -> ShowS
show :: ScottyException -> String
$cshow :: ScottyException -> String
showsPrec :: Int -> ScottyException -> ShowS
$cshowsPrec :: Int -> ScottyException -> ShowS
Show, Typeable)
instance Exception ScottyException
type Param = (Text, Text)
type File = (Text, FileInfo ByteString)
data ActionEnv = Env { ActionEnv -> Request
getReq :: Request
, ActionEnv -> [Param]
getParams :: [Param]
, ActionEnv -> IO ByteString
getBody :: IO ByteString
, ActionEnv -> IO ByteString
getBodyChunk :: IO BS.ByteString
, ActionEnv -> [File]
getFiles :: [File]
}
data RequestBodyState = BodyUntouched
| BodyCached ByteString [BS.ByteString]
| BodyCorrupted
data BodyPartiallyStreamed = BodyPartiallyStreamed deriving (Int -> BodyPartiallyStreamed -> ShowS
[BodyPartiallyStreamed] -> ShowS
BodyPartiallyStreamed -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BodyPartiallyStreamed] -> ShowS
$cshowList :: [BodyPartiallyStreamed] -> ShowS
show :: BodyPartiallyStreamed -> String
$cshow :: BodyPartiallyStreamed -> String
showsPrec :: Int -> BodyPartiallyStreamed -> ShowS
$cshowsPrec :: Int -> BodyPartiallyStreamed -> ShowS
Show, Typeable)
instance E.Exception BodyPartiallyStreamed
data Content = ContentBuilder Builder
| ContentFile FilePath
| ContentStream StreamingBody
data ScottyResponse = SR { ScottyResponse -> Status
srStatus :: Status
, :: ResponseHeaders
, ScottyResponse -> Content
srContent :: Content
}
instance Default ScottyResponse where
def :: ScottyResponse
def = Status -> ResponseHeaders -> Content -> ScottyResponse
SR Status
status200 [] (Builder -> Content
ContentBuilder forall a. Monoid a => a
mempty)
newtype ActionT e m a = ActionT { forall e (m :: * -> *) a.
ActionT e m a
-> ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
runAM :: ExceptT (ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a }
deriving ( forall a b. a -> ActionT e m b -> ActionT e m a
forall a b. (a -> b) -> ActionT e m a -> ActionT e m b
forall e (m :: * -> *) a b.
Functor m =>
a -> ActionT e m b -> ActionT e m a
forall e (m :: * -> *) a b.
Functor m =>
(a -> b) -> ActionT e m a -> ActionT e m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> ActionT e m b -> ActionT e m a
$c<$ :: forall e (m :: * -> *) a b.
Functor m =>
a -> ActionT e m b -> ActionT e m a
fmap :: forall a b. (a -> b) -> ActionT e m a -> ActionT e m b
$cfmap :: forall e (m :: * -> *) a b.
Functor m =>
(a -> b) -> ActionT e m a -> ActionT e m b
Functor, forall a. a -> ActionT e m a
forall a b. ActionT e m a -> ActionT e m b -> ActionT e m a
forall a b. ActionT e m a -> ActionT e m b -> ActionT e m b
forall a b. ActionT e m (a -> b) -> ActionT e m a -> ActionT e m b
forall a b c.
(a -> b -> c) -> ActionT e m a -> ActionT e m b -> ActionT e m c
forall {e} {m :: * -> *}. Monad m => Functor (ActionT e m)
forall e (m :: * -> *) a. Monad m => a -> ActionT e m a
forall e (m :: * -> *) a b.
Monad m =>
ActionT e m a -> ActionT e m b -> ActionT e m a
forall e (m :: * -> *) a b.
Monad m =>
ActionT e m a -> ActionT e m b -> ActionT e m b
forall e (m :: * -> *) a b.
Monad m =>
ActionT e m (a -> b) -> ActionT e m a -> ActionT e m b
forall e (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> ActionT e m a -> ActionT e m b -> ActionT e m c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: forall a b. ActionT e m a -> ActionT e m b -> ActionT e m a
$c<* :: forall e (m :: * -> *) a b.
Monad m =>
ActionT e m a -> ActionT e m b -> ActionT e m a
*> :: forall a b. ActionT e m a -> ActionT e m b -> ActionT e m b
$c*> :: forall e (m :: * -> *) a b.
Monad m =>
ActionT e m a -> ActionT e m b -> ActionT e m b
liftA2 :: forall a b c.
(a -> b -> c) -> ActionT e m a -> ActionT e m b -> ActionT e m c
$cliftA2 :: forall e (m :: * -> *) a b c.
Monad m =>
(a -> b -> c) -> ActionT e m a -> ActionT e m b -> ActionT e m c
<*> :: forall a b. ActionT e m (a -> b) -> ActionT e m a -> ActionT e m b
$c<*> :: forall e (m :: * -> *) a b.
Monad m =>
ActionT e m (a -> b) -> ActionT e m a -> ActionT e m b
pure :: forall a. a -> ActionT e m a
$cpure :: forall e (m :: * -> *) a. Monad m => a -> ActionT e m a
Applicative, forall a. IO a -> ActionT e m a
forall {e} {m :: * -> *}.
(ScottyError e, MonadIO m) =>
Monad (ActionT e m)
forall e (m :: * -> *) a.
(ScottyError e, MonadIO m) =>
IO a -> ActionT e m a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: forall a. IO a -> ActionT e m a
$cliftIO :: forall e (m :: * -> *) a.
(ScottyError e, MonadIO m) =>
IO a -> ActionT e m a
MonadIO )
instance (Monad m, ScottyError e) => Monad.Monad (ActionT e m) where
return :: forall a. a -> ActionT e m a
return = forall e (m :: * -> *) a.
ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
-> ActionT e m a
ActionT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => a -> m a
return
ActionT ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
m >>= :: forall a b. ActionT e m a -> (a -> ActionT e m b) -> ActionT e m b
>>= a -> ActionT e m b
k = forall e (m :: * -> *) a.
ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
-> ActionT e m a
ActionT (ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
m forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall e (m :: * -> *) a.
ActionT e m a
-> ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
runAM forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ActionT e m b
k)
#if !(MIN_VERSION_base(4,13,0))
fail = Fail.fail
#endif
instance (Monad m, ScottyError e) => Fail.MonadFail (ActionT e m) where
fail :: forall a. String -> ActionT e m a
fail = forall e (m :: * -> *) a.
ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
-> ActionT e m a
ActionT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e. ScottyError e => String -> e
stringError
instance ( Monad m, ScottyError e
#if !(MIN_VERSION_base(4,8,0))
, Functor m
#endif
) => Alternative (ActionT e m) where
empty :: forall a. ActionT e m a
empty = forall (m :: * -> *) a. MonadPlus m => m a
mzero
<|> :: forall a. ActionT e m a -> ActionT e m a -> ActionT e m a
(<|>) = forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
mplus
instance (Monad m, ScottyError e) => MonadPlus (ActionT e m) where
mzero :: forall a. ActionT e m a
mzero = forall e (m :: * -> *) a.
ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
-> ActionT e m a
ActionT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left forall e. ActionError e
Next
ActionT ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
m mplus :: forall a. ActionT e m a -> ActionT e m a -> ActionT e m a
`mplus` ActionT ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
n = forall e (m :: * -> *) a.
ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
-> ActionT e m a
ActionT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT forall a b. (a -> b) -> a -> b
$ do
Either (ActionError e) a
a <- forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
m
case Either (ActionError e) a
a of
Left ActionError e
_ -> forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
n
Right a
r -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right a
r
instance ScottyError e => MonadTrans (ActionT e) where
lift :: forall (m :: * -> *) a. Monad m => m a -> ActionT e m a
lift = forall e (m :: * -> *) a.
ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
-> ActionT e m a
ActionT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift
instance (ScottyError e, Monad m) => MonadError (ActionError e) (ActionT e m) where
throwError :: forall a. ActionError e -> ActionT e m a
throwError = forall e (m :: * -> *) a.
ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
-> ActionT e m a
ActionT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError
catchError :: forall a.
ActionT e m a -> (ActionError e -> ActionT e m a) -> ActionT e m a
catchError (ActionT ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
m) ActionError e -> ActionT e m a
f = forall e (m :: * -> *) a.
ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
-> ActionT e m a
ActionT (forall e (m :: * -> *) a.
MonadError e m =>
m a -> (e -> m a) -> m a
catchError ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
m (forall e (m :: * -> *) a.
ActionT e m a
-> ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
runAM forall b c a. (b -> c) -> (a -> b) -> a -> c
. ActionError e -> ActionT e m a
f))
instance (MonadBase b m, ScottyError e) => MonadBase b (ActionT e m) where
liftBase :: forall α. b α -> ActionT e m α
liftBase = forall (t :: (* -> *) -> * -> *) (b :: * -> *) (m :: * -> *) α.
(MonadTrans t, MonadBase b m) =>
b α -> t m α
liftBaseDefault
instance (MonadThrow m, ScottyError e) => MonadThrow (ActionT e m) where
throwM :: forall e a. Exception e => e -> ActionT e m a
throwM = forall e (m :: * -> *) a.
ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
-> ActionT e m a
ActionT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM
instance (MonadCatch m, ScottyError e) => MonadCatch (ActionT e m) where
catch :: forall e a.
Exception e =>
ActionT e m a -> (e -> ActionT e m a) -> ActionT e m a
catch (ActionT ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
m) e -> ActionT e m a
f = forall e (m :: * -> *) a.
ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
-> ActionT e m a
ActionT (ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
m forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
`catch` (forall e (m :: * -> *) a.
ActionT e m a
-> ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
runAM forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> ActionT e m a
f))
instance ScottyError e => MonadTransControl (ActionT e) where
type StT (ActionT e) a = StT (StateT ScottyResponse) (StT (ReaderT ActionEnv) (StT (ExceptT (ActionError e)) a))
liftWith :: forall (m :: * -> *) a.
Monad m =>
(Run (ActionT e) -> m a) -> ActionT e m a
liftWith = \Run (ActionT e) -> m a
f ->
forall e (m :: * -> *) a.
ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
-> ActionT e m a
ActionT forall a b. (a -> b) -> a -> b
$ forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTransControl t, Monad m) =>
(Run t -> m a) -> t m a
liftWith forall a b. (a -> b) -> a -> b
$ \Run (ExceptT (ActionError e))
run ->
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTransControl t, Monad m) =>
(Run t -> m a) -> t m a
liftWith forall a b. (a -> b) -> a -> b
$ \Run (ReaderT ActionEnv)
run' ->
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTransControl t, Monad m) =>
(Run t -> m a) -> t m a
liftWith forall a b. (a -> b) -> a -> b
$ \Run (StateT ScottyResponse)
run'' ->
Run (ActionT e) -> m a
f forall a b. (a -> b) -> a -> b
$ Run (StateT ScottyResponse)
run'' forall b c a. (b -> c) -> (a -> b) -> a -> c
. Run (ReaderT ActionEnv)
run' forall b c a. (b -> c) -> (a -> b) -> a -> c
. Run (ExceptT (ActionError e))
run forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (m :: * -> *) a.
ActionT e m a
-> ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
runAM
restoreT :: forall (m :: * -> *) a.
Monad m =>
m (StT (ActionT e) a) -> ActionT e m a
restoreT = forall e (m :: * -> *) a.
ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
-> ActionT e m a
ActionT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTransControl t, Monad m) =>
m (StT t a) -> t m a
restoreT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTransControl t, Monad m) =>
m (StT t a) -> t m a
restoreT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTransControl t, Monad m) =>
m (StT t a) -> t m a
restoreT
instance (ScottyError e, MonadBaseControl b m) => MonadBaseControl b (ActionT e m) where
type StM (ActionT e m) a = ComposeSt (ActionT e) m a
liftBaseWith :: forall a. (RunInBase (ActionT e m) b -> b a) -> ActionT e m a
liftBaseWith = forall (t :: (* -> *) -> * -> *) (b :: * -> *) (m :: * -> *) a.
(MonadTransControl t, MonadBaseControl b m) =>
(RunInBaseDefault t m b -> b a) -> t m a
defaultLiftBaseWith
restoreM :: forall a. StM (ActionT e m) a -> ActionT e m a
restoreM = forall (t :: (* -> *) -> * -> *) (b :: * -> *) (m :: * -> *) a.
(MonadTransControl t, MonadBaseControl b m) =>
ComposeSt t m a -> t m a
defaultRestoreM
instance (MonadReader r m, ScottyError e) => MonadReader r (ActionT e m) where
{-# INLINE ask #-}
ask :: ActionT e m r
ask = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall r (m :: * -> *). MonadReader r m => m r
ask
{-# INLINE local #-}
local :: forall a. (r -> r) -> ActionT e m a -> ActionT e m a
local r -> r
f = forall e (m :: * -> *) a.
ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
-> ActionT e m a
ActionT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) e a (n :: * -> *) e' b.
(m (Either e a) -> n (Either e' b))
-> ExceptT e m a -> ExceptT e' n b
mapExceptT (forall (m :: * -> *) a (n :: * -> *) b r.
(m a -> n b) -> ReaderT r m a -> ReaderT r n b
mapReaderT (forall (m :: * -> *) a s (n :: * -> *) b.
(m (a, s) -> n (b, s)) -> StateT s m a -> StateT s n b
mapStateT forall a b. (a -> b) -> a -> b
$ forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local r -> r
f)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (m :: * -> *) a.
ActionT e m a
-> ExceptT
(ActionError e) (ReaderT ActionEnv (StateT ScottyResponse m)) a
runAM
instance (MonadState s m, ScottyError e) => MonadState s (ActionT e m) where
{-# INLINE get #-}
get :: ActionT e m s
get = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall s (m :: * -> *). MonadState s m => m s
get
{-# INLINE put #-}
put :: s -> ActionT e m ()
put = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s (m :: * -> *). MonadState s m => s -> m ()
put
instance (Semigroup a) => Semigroup (ScottyT e m a) where
ScottyT e m a
x <> :: ScottyT e m a -> ScottyT e m a -> ScottyT e m a
<> ScottyT e m a
y = forall a. Semigroup a => a -> a -> a
(<>) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ScottyT e m a
x forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ScottyT e m a
y
instance
( Monoid a
#if !(MIN_VERSION_base(4,11,0))
, Semigroup a
#endif
#if !(MIN_VERSION_base(4,8,0))
, Functor m
#endif
) => Monoid (ScottyT e m a) where
mempty :: ScottyT e m a
mempty = forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Monoid a => a
mempty
#if !(MIN_VERSION_base(4,11,0))
mappend = (<>)
#endif
instance
( Monad m
#if !(MIN_VERSION_base(4,8,0))
, Functor m
#endif
, Semigroup a
) => Semigroup (ActionT e m a) where
ActionT e m a
x <> :: ActionT e m a -> ActionT e m a -> ActionT e m a
<> ActionT e m a
y = forall a. Semigroup a => a -> a -> a
(<>) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT e m a
x forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT e m a
y
instance
( Monad m, ScottyError e, Monoid a
#if !(MIN_VERSION_base(4,11,0))
, Semigroup a
#endif
#if !(MIN_VERSION_base(4,8,0))
, Functor m
#endif
) => Monoid (ActionT e m a) where
mempty :: ActionT e m a
mempty = forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Monoid a => a
mempty
#if !(MIN_VERSION_base(4,11,0))
mappend = (<>)
#endif
data RoutePattern = Capture Text
| Literal Text
| Function (Request -> Maybe [Param])
instance IsString RoutePattern where
fromString :: String -> RoutePattern
fromString = Text -> RoutePattern
Capture forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack