{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# language ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE RecordWildCards #-}
module Web.Scotty.Internal.Types where

import           Blaze.ByteString.Builder (Builder)

import           Control.Applicative
import Control.Concurrent.MVar
import Control.Concurrent.STM (TVar, atomically, readTVarIO, modifyTVar')
import qualified Control.Exception as E
import           Control.Monad (MonadPlus(..))
import           Control.Monad.Base (MonadBase)
import           Control.Monad.Catch (MonadCatch, MonadThrow)
import           Control.Monad.Error.Class (MonadError(..))
import           Control.Monad.IO.Class (MonadIO(..))
import UnliftIO (MonadUnliftIO(..))
import           Control.Monad.Reader (MonadReader(..), ReaderT, asks)
import           Control.Monad.State.Strict (State, StateT(..))
import           Control.Monad.Trans.Class (MonadTrans(..))
import           Control.Monad.Trans.Control (MonadBaseControl, MonadTransControl)

import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy.Char8 as LBS8 (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 Web.Scotty.Exceptions (Handler(..), catch, catches)


--------------------- Options -----------------------
data Options = Options { Options -> Int
verbose :: Int -- ^ 0 = silent, 1(def) = startup banner
                       , Options -> Settings
settings :: Settings -- ^ Warp 'Settings'
                                              -- Note: to work around an issue in warp,
                                              -- the default FD cache duration is set to 0
                                              -- so changes to static files are always picked
                                              -- up. This likely has performance implications,
                                              -- so you may want to modify this for production
                                              -- servers using `setFdCacheDuration`.
                       }

instance Default Options where
  def :: Options
def = Options
defaultOptions

defaultOptions :: Options
defaultOptions :: Options
defaultOptions = Int -> Settings -> Options
Options Int
1 Settings
defaultSettings

newtype RouteOptions = RouteOptions { RouteOptions -> Maybe Int
maxRequestBodySize :: Maybe Kilobytes -- max allowed request size in KB
                                    }

instance Default RouteOptions where
    def :: RouteOptions
def = RouteOptions
defaultRouteOptions

defaultRouteOptions :: RouteOptions
defaultRouteOptions :: RouteOptions
defaultRouteOptions = Maybe Int -> RouteOptions
RouteOptions forall a. Maybe a
Nothing

type Kilobytes = Int
----- Transformer Aware Applications/Middleware -----
type Middleware m = Application m -> Application m
type Application m = Request -> m Response

------------------ Scotty Request Body --------------------

data BodyChunkBuffer = BodyChunkBuffer { BodyChunkBuffer -> Bool
hasFinishedReadingChunks :: Bool -- ^ whether we've reached the end of the stream yet
                                       , BodyChunkBuffer -> [ByteString]
chunksReadSoFar :: [BS.ByteString]
                                       }
-- | The key part of having two MVars is that we can "clone" the BodyInfo to create a copy where the index is reset to 0, but the chunk cache is the same. Passing a cloned BodyInfo into each matched route allows them each to start from the first chunk if they call bodyReader.
--
-- Introduced in (#308)
data BodyInfo = BodyInfo { BodyInfo -> MVar Int
bodyInfoReadProgress :: MVar Int -- ^ index into the stream read so far
                         , BodyInfo -> MVar BodyChunkBuffer
bodyInfoChunkBuffer :: MVar BodyChunkBuffer
                         , BodyInfo -> IO ByteString
bodyInfoDirectChunkRead :: IO BS.ByteString -- ^ can be called to get more chunks
                         }

--------------- Scotty Applications -----------------

data ScottyState m =
    ScottyState { forall (m :: * -> *). ScottyState m -> [Middleware]
middlewares :: [Wai.Middleware]
                , forall (m :: * -> *). ScottyState m -> [BodyInfo -> Middleware m]
routes :: [BodyInfo -> Middleware m]
                , forall (m :: * -> *). ScottyState m -> Maybe (ErrorHandler m)
handler :: Maybe (ErrorHandler m)
                , forall (m :: * -> *). ScottyState m -> RouteOptions
routeOptions :: RouteOptions
                }

instance Default (ScottyState m) where
  def :: ScottyState m
def = forall (m :: * -> *). ScottyState m
defaultScottyState

defaultScottyState :: ScottyState m
defaultScottyState :: forall (m :: * -> *). ScottyState m
defaultScottyState = forall (m :: * -> *).
[Middleware]
-> [BodyInfo -> Middleware m]
-> Maybe (ErrorHandler m)
-> RouteOptions
-> ScottyState m
ScottyState [] [] forall a. Maybe a
Nothing RouteOptions
defaultRouteOptions

addMiddleware :: Wai.Middleware -> ScottyState m -> ScottyState m
addMiddleware :: forall (m :: * -> *). Middleware -> ScottyState m -> ScottyState m
addMiddleware Middleware
m s :: ScottyState m
s@(ScottyState {middlewares :: forall (m :: * -> *). ScottyState m -> [Middleware]
middlewares = [Middleware]
ms}) = ScottyState m
s { middlewares :: [Middleware]
middlewares = Middleware
mforall a. a -> [a] -> [a]
:[Middleware]
ms }

addRoute :: (BodyInfo -> Middleware m) -> ScottyState m -> ScottyState m
addRoute :: forall (m :: * -> *).
(BodyInfo -> Middleware m) -> ScottyState m -> ScottyState m
addRoute BodyInfo -> Middleware m
r s :: ScottyState m
s@(ScottyState {routes :: forall (m :: * -> *). ScottyState m -> [BodyInfo -> Middleware m]
routes = [BodyInfo -> Middleware m]
rs}) = ScottyState m
s { routes :: [BodyInfo -> Middleware m]
routes = BodyInfo -> Middleware m
rforall a. a -> [a] -> [a]
:[BodyInfo -> Middleware m]
rs }

setHandler :: Maybe (ErrorHandler m) -> ScottyState m -> ScottyState m
setHandler :: forall (m :: * -> *).
Maybe (ErrorHandler m) -> ScottyState m -> ScottyState m
setHandler Maybe (ErrorHandler m)
h ScottyState m
s = ScottyState m
s { handler :: Maybe (ErrorHandler m)
handler = Maybe (ErrorHandler m)
h }

updateMaxRequestBodySize :: RouteOptions -> ScottyState m -> ScottyState m
updateMaxRequestBodySize :: forall (m :: * -> *).
RouteOptions -> ScottyState m -> ScottyState m
updateMaxRequestBodySize RouteOptions { Maybe Int
maxRequestBodySize :: Maybe Int
maxRequestBodySize :: RouteOptions -> Maybe Int
.. } s :: ScottyState m
s@ScottyState { routeOptions :: forall (m :: * -> *). ScottyState m -> RouteOptions
routeOptions = RouteOptions
ro } =
    let ro' :: RouteOptions
ro' = RouteOptions
ro { maxRequestBodySize :: Maybe Int
maxRequestBodySize = Maybe Int
maxRequestBodySize }
    in ScottyState m
s { routeOptions :: RouteOptions
routeOptions = RouteOptions
ro' }

newtype ScottyT m a = ScottyT { forall (m :: * -> *) a. ScottyT m a -> State (ScottyState m) a
runS :: State (ScottyState m) a }
    deriving ( forall a b. a -> ScottyT m b -> ScottyT m a
forall a b. (a -> b) -> ScottyT m a -> ScottyT m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
forall (m :: * -> *) a b. a -> ScottyT m b -> ScottyT m a
forall (m :: * -> *) a b. (a -> b) -> ScottyT m a -> ScottyT m b
<$ :: forall a b. a -> ScottyT m b -> ScottyT m a
$c<$ :: forall (m :: * -> *) a b. a -> ScottyT m b -> ScottyT m a
fmap :: forall a b. (a -> b) -> ScottyT m a -> ScottyT m b
$cfmap :: forall (m :: * -> *) a b. (a -> b) -> ScottyT m a -> ScottyT m b
Functor, forall a. a -> ScottyT m a
forall a b. ScottyT m a -> ScottyT m b -> ScottyT m a
forall a b. ScottyT m a -> ScottyT m b -> ScottyT m b
forall a b. ScottyT m (a -> b) -> ScottyT m a -> ScottyT m b
forall a b c.
(a -> b -> c) -> ScottyT m a -> ScottyT m b -> ScottyT m c
forall (m :: * -> *). Functor (ScottyT m)
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 (m :: * -> *) a. a -> ScottyT m a
forall (m :: * -> *) a b. ScottyT m a -> ScottyT m b -> ScottyT m a
forall (m :: * -> *) a b. ScottyT m a -> ScottyT m b -> ScottyT m b
forall (m :: * -> *) a b.
ScottyT m (a -> b) -> ScottyT m a -> ScottyT m b
forall (m :: * -> *) a b c.
(a -> b -> c) -> ScottyT m a -> ScottyT m b -> ScottyT m c
<* :: forall a b. ScottyT m a -> ScottyT m b -> ScottyT m a
$c<* :: forall (m :: * -> *) a b. ScottyT m a -> ScottyT m b -> ScottyT m a
*> :: forall a b. ScottyT m a -> ScottyT m b -> ScottyT m b
$c*> :: forall (m :: * -> *) a b. ScottyT m a -> ScottyT m b -> ScottyT m b
liftA2 :: forall a b c.
(a -> b -> c) -> ScottyT m a -> ScottyT m b -> ScottyT m c
$cliftA2 :: forall (m :: * -> *) a b c.
(a -> b -> c) -> ScottyT m a -> ScottyT m b -> ScottyT m c
<*> :: forall a b. ScottyT m (a -> b) -> ScottyT m a -> ScottyT m b
$c<*> :: forall (m :: * -> *) a b.
ScottyT m (a -> b) -> ScottyT m a -> ScottyT m b
pure :: forall a. a -> ScottyT m a
$cpure :: forall (m :: * -> *) a. a -> ScottyT m a
Applicative, forall a. a -> ScottyT m a
forall a b. ScottyT m a -> ScottyT m b -> ScottyT m b
forall a b. ScottyT m a -> (a -> ScottyT m b) -> ScottyT m b
forall (m :: * -> *). Applicative (ScottyT m)
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
forall (m :: * -> *) a. a -> ScottyT m a
forall (m :: * -> *) a b. ScottyT m a -> ScottyT m b -> ScottyT m b
forall (m :: * -> *) a b.
ScottyT m a -> (a -> ScottyT m b) -> ScottyT m b
return :: forall a. a -> ScottyT m a
$creturn :: forall (m :: * -> *) a. a -> ScottyT m a
>> :: forall a b. ScottyT m a -> ScottyT m b -> ScottyT m b
$c>> :: forall (m :: * -> *) a b. ScottyT m a -> ScottyT m b -> ScottyT m b
>>= :: forall a b. ScottyT m a -> (a -> ScottyT m b) -> ScottyT m b
$c>>= :: forall (m :: * -> *) a b.
ScottyT m a -> (a -> ScottyT m b) -> ScottyT m b
Monad )


------------------ Scotty Errors --------------------

-- | Internal exception mechanism used to modify the request processing flow.
--
-- The exception constructor is not exposed to the user and all exceptions of this type are caught
-- and processed within the 'runAction' function.
data ActionError
  = AERedirect Text -- ^ Redirect
  | AENext -- ^ Stop processing this route and skip to the next one
  | AEFinish -- ^ Stop processing the request
  deriving (Int -> ActionError -> ShowS
[ActionError] -> ShowS
ActionError -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ActionError] -> ShowS
$cshowList :: [ActionError] -> ShowS
show :: ActionError -> String
$cshow :: ActionError -> String
showsPrec :: Int -> ActionError -> ShowS
$cshowsPrec :: Int -> ActionError -> ShowS
Show, Typeable)
instance E.Exception ActionError

tryNext :: MonadUnliftIO m => m a -> m Bool
tryNext :: forall (m :: * -> *) a. MonadUnliftIO m => m a -> m Bool
tryNext m a
io = forall (m :: * -> *) e a.
(MonadUnliftIO m, Exception e) =>
m a -> (e -> m a) -> m a
catch (m a
io forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True) forall a b. (a -> b) -> a -> b
$ \ActionError
e ->
  case ActionError
e of
    ActionError
AENext -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
    ActionError
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True

-- | E.g. when a parameter is not found in a query string (400 Bad Request) or when parsing a JSON body fails (422 Unprocessable Entity)
data StatusError = StatusError Status Text deriving (Int -> StatusError -> ShowS
[StatusError] -> ShowS
StatusError -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StatusError] -> ShowS
$cshowList :: [StatusError] -> ShowS
show :: StatusError -> String
$cshow :: StatusError -> String
showsPrec :: Int -> StatusError -> ShowS
$cshowsPrec :: Int -> StatusError -> ShowS
Show, Typeable)
instance E.Exception StatusError

-- | Specializes a 'Handler' to the 'ActionT' monad
type ErrorHandler m = Handler (ActionT m) ()

-- | Thrown e.g. when a request is too large
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 E.Exception ScottyException

------------------ Scotty Actions -------------------
type Param = (Text, Text)

type File = (Text, FileInfo LBS8.ByteString)

data ActionEnv = Env { ActionEnv -> Request
envReq       :: Request
                     , ActionEnv -> [Param]
envCaptureParams :: [Param]
                     , ActionEnv -> [Param]
envFormParams    :: [Param]
                     , ActionEnv -> [Param]
envQueryParams :: [Param]
                     , ActionEnv -> IO ByteString
envBody      :: IO LBS8.ByteString
                     , ActionEnv -> IO ByteString
envBodyChunk :: IO BS.ByteString
                     , ActionEnv -> [File]
envFiles     :: [File]
                     , ActionEnv -> TVar ScottyResponse
envResponse :: TVar ScottyResponse
                     }

getResponse :: MonadIO m => ActionEnv -> m ScottyResponse
getResponse :: forall (m :: * -> *). MonadIO m => ActionEnv -> m ScottyResponse
getResponse ActionEnv
ae = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. TVar a -> IO a
readTVarIO (ActionEnv -> TVar ScottyResponse
envResponse ActionEnv
ae)

modifyResponse :: (MonadIO m) => (ScottyResponse -> ScottyResponse) -> ActionT m ()
modifyResponse :: forall (m :: * -> *).
MonadIO m =>
(ScottyResponse -> ScottyResponse) -> ActionT m ()
modifyResponse ScottyResponse -> ScottyResponse
f = do
  TVar ScottyResponse
tv <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks ActionEnv -> TVar ScottyResponse
envResponse
  forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar ScottyResponse
tv ScottyResponse -> ScottyResponse
f

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
             | ContentResponse Response

data ScottyResponse = SR { ScottyResponse -> Status
srStatus  :: Status
                         , ScottyResponse -> ResponseHeaders
srHeaders :: ResponseHeaders
                         , ScottyResponse -> Content
srContent :: Content
                         }

setContent :: Content -> ScottyResponse -> ScottyResponse
setContent :: Content -> ScottyResponse -> ScottyResponse
setContent Content
c ScottyResponse
sr = ScottyResponse
sr { srContent :: Content
srContent = Content
c }

setHeaderWith :: ([(HeaderName, BS.ByteString)] -> [(HeaderName, BS.ByteString)]) -> ScottyResponse -> ScottyResponse
setHeaderWith :: (ResponseHeaders -> ResponseHeaders)
-> ScottyResponse -> ScottyResponse
setHeaderWith ResponseHeaders -> ResponseHeaders
f ScottyResponse
sr = ScottyResponse
sr { srHeaders :: ResponseHeaders
srHeaders = ResponseHeaders -> ResponseHeaders
f (ScottyResponse -> ResponseHeaders
srHeaders ScottyResponse
sr) }

setStatus :: Status -> ScottyResponse -> ScottyResponse
setStatus :: Status -> ScottyResponse -> ScottyResponse
setStatus Status
s ScottyResponse
sr = ScottyResponse
sr { srStatus :: Status
srStatus = Status
s }

instance Default ScottyResponse where
  def :: ScottyResponse
def = ScottyResponse
defaultScottyResponse

-- | The default response has code 200 OK and empty body
defaultScottyResponse :: ScottyResponse
defaultScottyResponse :: ScottyResponse
defaultScottyResponse = Status -> ResponseHeaders -> Content -> ScottyResponse
SR Status
status200 [] (Builder -> Content
ContentBuilder forall a. Monoid a => a
mempty)


newtype ActionT m a = ActionT { forall (m :: * -> *) a. ActionT m a -> ReaderT ActionEnv m a
runAM :: ReaderT ActionEnv m a }
  deriving newtype (forall a b. a -> ActionT m b -> ActionT m a
forall a b. (a -> b) -> ActionT m a -> ActionT m b
forall (m :: * -> *) a b.
Functor m =>
a -> ActionT m b -> ActionT m a
forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> ActionT m a -> ActionT 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 m b -> ActionT m a
$c<$ :: forall (m :: * -> *) a b.
Functor m =>
a -> ActionT m b -> ActionT m a
fmap :: forall a b. (a -> b) -> ActionT m a -> ActionT m b
$cfmap :: forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> ActionT m a -> ActionT m b
Functor, forall a. a -> ActionT m a
forall a b. ActionT m a -> ActionT m b -> ActionT m a
forall a b. ActionT m a -> ActionT m b -> ActionT m b
forall a b. ActionT m (a -> b) -> ActionT m a -> ActionT m b
forall a b c.
(a -> b -> c) -> ActionT m a -> ActionT m b -> ActionT 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 {m :: * -> *}. Applicative m => Functor (ActionT m)
forall (m :: * -> *) a. Applicative m => a -> ActionT m a
forall (m :: * -> *) a b.
Applicative m =>
ActionT m a -> ActionT m b -> ActionT m a
forall (m :: * -> *) a b.
Applicative m =>
ActionT m a -> ActionT m b -> ActionT m b
forall (m :: * -> *) a b.
Applicative m =>
ActionT m (a -> b) -> ActionT m a -> ActionT m b
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c) -> ActionT m a -> ActionT m b -> ActionT m c
<* :: forall a b. ActionT m a -> ActionT m b -> ActionT m a
$c<* :: forall (m :: * -> *) a b.
Applicative m =>
ActionT m a -> ActionT m b -> ActionT m a
*> :: forall a b. ActionT m a -> ActionT m b -> ActionT m b
$c*> :: forall (m :: * -> *) a b.
Applicative m =>
ActionT m a -> ActionT m b -> ActionT m b
liftA2 :: forall a b c.
(a -> b -> c) -> ActionT m a -> ActionT m b -> ActionT m c
$cliftA2 :: forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c) -> ActionT m a -> ActionT m b -> ActionT m c
<*> :: forall a b. ActionT m (a -> b) -> ActionT m a -> ActionT m b
$c<*> :: forall (m :: * -> *) a b.
Applicative m =>
ActionT m (a -> b) -> ActionT m a -> ActionT m b
pure :: forall a. a -> ActionT m a
$cpure :: forall (m :: * -> *) a. Applicative m => a -> ActionT m a
Applicative, forall a. a -> ActionT m a
forall a b. ActionT m a -> ActionT m b -> ActionT m b
forall a b. ActionT m a -> (a -> ActionT m b) -> ActionT m b
forall {m :: * -> *}. Monad m => Applicative (ActionT m)
forall (m :: * -> *) a. Monad m => a -> ActionT m a
forall (m :: * -> *) a b.
Monad m =>
ActionT m a -> ActionT m b -> ActionT m b
forall (m :: * -> *) a b.
Monad m =>
ActionT m a -> (a -> ActionT m b) -> ActionT 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 -> ActionT m a
$creturn :: forall (m :: * -> *) a. Monad m => a -> ActionT m a
>> :: forall a b. ActionT m a -> ActionT m b -> ActionT m b
$c>> :: forall (m :: * -> *) a b.
Monad m =>
ActionT m a -> ActionT m b -> ActionT m b
>>= :: forall a b. ActionT m a -> (a -> ActionT m b) -> ActionT m b
$c>>= :: forall (m :: * -> *) a b.
Monad m =>
ActionT m a -> (a -> ActionT m b) -> ActionT m b
Monad, forall a. IO a -> ActionT m a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
forall {m :: * -> *}. MonadIO m => Monad (ActionT m)
forall (m :: * -> *) a. MonadIO m => IO a -> ActionT m a
liftIO :: forall a. IO a -> ActionT m a
$cliftIO :: forall (m :: * -> *) a. MonadIO m => IO a -> ActionT m a
MonadIO, MonadReader ActionEnv, forall (m :: * -> *) a. Monad m => m a -> ActionT m a
forall (t :: (* -> *) -> * -> *).
(forall (m :: * -> *) a. Monad m => m a -> t m a) -> MonadTrans t
lift :: forall (m :: * -> *) a. Monad m => m a -> ActionT m a
$clift :: forall (m :: * -> *) a. Monad m => m a -> ActionT m a
MonadTrans, forall e a. Exception e => e -> ActionT m a
forall (m :: * -> *).
Monad m -> (forall e a. Exception e => e -> m a) -> MonadThrow m
forall {m :: * -> *}. MonadThrow m => Monad (ActionT m)
forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> ActionT m a
throwM :: forall e a. Exception e => e -> ActionT m a
$cthrowM :: forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> ActionT m a
MonadThrow, forall e a.
Exception e =>
ActionT m a -> (e -> ActionT m a) -> ActionT m a
forall (m :: * -> *).
MonadThrow m
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> MonadCatch m
forall {m :: * -> *}. MonadCatch m => MonadThrow (ActionT m)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
ActionT m a -> (e -> ActionT m a) -> ActionT m a
catch :: forall e a.
Exception e =>
ActionT m a -> (e -> ActionT m a) -> ActionT m a
$ccatch :: forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
ActionT m a -> (e -> ActionT m a) -> ActionT m a
MonadCatch, MonadBase b, MonadBaseControl b, MonadTrans ActionT
forall (m :: * -> *) a. Monad m => m (StT ActionT a) -> ActionT m a
forall (m :: * -> *) a.
Monad m =>
(Run ActionT -> m a) -> ActionT m a
forall (t :: (* -> *) -> * -> *).
MonadTrans t
-> (forall (m :: * -> *) a. Monad m => (Run t -> m a) -> t m a)
-> (forall (m :: * -> *) a. Monad m => m (StT t a) -> t m a)
-> MonadTransControl t
restoreT :: forall (m :: * -> *) a. Monad m => m (StT ActionT a) -> ActionT m a
$crestoreT :: forall (m :: * -> *) a. Monad m => m (StT ActionT a) -> ActionT m a
liftWith :: forall (m :: * -> *) a.
Monad m =>
(Run ActionT -> m a) -> ActionT m a
$cliftWith :: forall (m :: * -> *) a.
Monad m =>
(Run ActionT -> m a) -> ActionT m a
MonadTransControl, forall b. ((forall a. ActionT m a -> IO a) -> IO b) -> ActionT m b
forall (m :: * -> *).
MonadIO m
-> (forall b. ((forall a. m a -> IO a) -> IO b) -> m b)
-> MonadUnliftIO m
forall {m :: * -> *}. MonadUnliftIO m => MonadIO (ActionT m)
forall (m :: * -> *) b.
MonadUnliftIO m =>
((forall a. ActionT m a -> IO a) -> IO b) -> ActionT m b
withRunInIO :: forall b. ((forall a. ActionT m a -> IO a) -> IO b) -> ActionT m b
$cwithRunInIO :: forall (m :: * -> *) b.
MonadUnliftIO m =>
((forall a. ActionT m a -> IO a) -> IO b) -> ActionT m b
MonadUnliftIO)

-- | Models the invariant that only 'StatusError's can be thrown and caught.
instance (MonadUnliftIO m) => MonadError StatusError (ActionT m) where
  throwError :: forall a. StatusError -> ActionT m a
throwError = forall a e. Exception e => e -> a
E.throw
  catchError :: forall a.
ActionT m a -> (StatusError -> ActionT m a) -> ActionT m a
catchError = forall (m :: * -> *) e a.
(MonadUnliftIO m, Exception e) =>
m a -> (e -> m a) -> m a
catch
-- | Modeled after the behaviour in scotty < 0.20, 'fail' throws a 'StatusError' with code 500 ("Server Error"), which can be caught with 'E.catch' or 'rescue'.
instance (MonadIO m) => MonadFail (ActionT m) where
  fail :: forall a. String -> ActionT m a
fail = forall a e. Exception e => e -> a
E.throw forall b c a. (b -> c) -> (a -> b) -> a -> c
. Status -> Text -> StatusError
StatusError Status
status500 forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack
-- | 'empty' throws 'ActionError' 'AENext', whereas '(<|>)' catches any 'ActionError's or 'StatusError's in the first action and proceeds to the second one.
instance (MonadUnliftIO m) => Alternative (ActionT m) where
  empty :: forall a. ActionT m a
empty = forall a e. Exception e => e -> a
E.throw ActionError
AENext
  ActionT m a
a <|> :: forall a. ActionT m a -> ActionT m a -> ActionT m a
<|> ActionT m a
b = do
    Bool
ok <- forall (m :: * -> *) a. MonadUnliftIO m => m a -> m Bool
tryAnyStatus ActionT m a
a
    if Bool
ok then ActionT m a
a else ActionT m a
b
instance (MonadUnliftIO m) => MonadPlus (ActionT m) where
  mzero :: forall a. ActionT m a
mzero = forall (f :: * -> *) a. Alternative f => f a
empty
  mplus :: forall a. ActionT m a -> ActionT m a -> ActionT m a
mplus = forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>)

-- | catches either ActionError (thrown by 'next') or 'StatusError' (thrown if e.g. a query parameter is not found)
tryAnyStatus :: MonadUnliftIO m => m a -> m Bool
tryAnyStatus :: forall (m :: * -> *) a. MonadUnliftIO m => m a -> m Bool
tryAnyStatus m a
io = (m a
io forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True) forall (m :: * -> *) a.
MonadUnliftIO m =>
m a -> [Handler m a] -> m a
`catches` [Handler m Bool
h1, Handler m Bool
h2]
  where
    h1 :: Handler m Bool
h1 = forall (m :: * -> *) a e. Exception e => (e -> m a) -> Handler m a
Handler forall a b. (a -> b) -> a -> b
$ \(ActionError
_ :: ActionError) -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
    h2 :: Handler m Bool
h2 = forall (m :: * -> *) a e. Exception e => (e -> m a) -> Handler m a
Handler forall a b. (a -> b) -> a -> b
$ \(StatusError
_ :: StatusError) -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False

instance (Semigroup a) => Semigroup (ScottyT m a) where
  ScottyT m a
x <> :: ScottyT m a -> ScottyT m a -> ScottyT m a
<> ScottyT m a
y = forall a. Semigroup a => a -> a -> a
(<>) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ScottyT m a
x forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ScottyT 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 m a) where
  mempty :: ScottyT 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 m a) where
  ActionT m a
x <> :: ActionT m a -> ActionT m a -> ActionT m a
<> ActionT m a
y = forall a. Semigroup a => a -> a -> a
(<>) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ActionT m a
x forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ActionT m a
y

instance
  ( Monad m, Monoid a
#if !(MIN_VERSION_base(4,11,0))
  , Semigroup a
#endif
#if !(MIN_VERSION_base(4,8,0))
  , Functor m
#endif
  ) => Monoid (ActionT m a) where
  mempty :: ActionT 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

------------------ Scotty Routes --------------------
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