scotty-0.30: Haskell web framework inspired by Ruby's Sinatra, using WAI and Warp
Safe HaskellNone
LanguageHaskell2010

Web.Scotty.Internal.Types

Synopsis

Documentation

data Options Source #

Constructors

Options 

Fields

  • verbose :: Int

    0 = silent, 1(def) = startup banner

  • 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.

  • jsonMode :: Bool

    If True, return JSON error responses instead of HTML

type Application (m :: Type -> Type) = Request -> m Response Source #

data BodyChunkBuffer Source #

Constructors

BodyChunkBuffer 

Fields

data BodyInfo Source #

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)

Constructors

BodyInfo 

Fields

setHandler :: forall (m :: Type -> Type). Maybe (ErrorHandler m) -> ScottyState m -> ScottyState m Source #

newtype ScottyT (m :: Type -> Type) a Source #

Constructors

ScottyT 

Fields

Instances

Instances details
Applicative (ScottyT m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

pure :: a -> ScottyT m a #

(<*>) :: ScottyT m (a -> b) -> ScottyT m a -> ScottyT m b #

liftA2 :: (a -> b -> c) -> ScottyT m a -> ScottyT m b -> ScottyT m c #

(*>) :: ScottyT m a -> ScottyT m b -> ScottyT m b #

(<*) :: ScottyT m a -> ScottyT m b -> ScottyT m a #

Functor (ScottyT m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

fmap :: (a -> b) -> ScottyT m a -> ScottyT m b #

(<$) :: a -> ScottyT m b -> ScottyT m a #

Monad (ScottyT m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

(>>=) :: ScottyT m a -> (a -> ScottyT m b) -> ScottyT m b #

(>>) :: ScottyT m a -> ScottyT m b -> ScottyT m b #

return :: a -> ScottyT m a #

Monoid a => Monoid (ScottyT m a) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

mempty :: ScottyT m a #

mappend :: ScottyT m a -> ScottyT m a -> ScottyT m a #

mconcat :: [ScottyT m a] -> ScottyT m a #

Semigroup a => Semigroup (ScottyT m a) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

(<>) :: ScottyT m a -> ScottyT m a -> ScottyT m a #

sconcat :: NonEmpty (ScottyT m a) -> ScottyT m a #

stimes :: Integral b => b -> ScottyT m a -> ScottyT m a #

data ActionError Source #

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.

Constructors

AERedirect Status Text

Redirect

AENext

Stop processing this route and skip to the next one

AEFinish

Stop processing the request

tryNext :: MonadUnliftIO m => m a -> m Bool Source #

type ErrorHandler (m :: Type -> Type) = Handler (ActionT m) () Source #

Specializes a Handler to the ActionT monad

type Param = (Text, Text) Source #

type File t = (Text, FileInfo t) Source #

Type parameter t is the file content. Could be () when not needed or a FilePath for temp files instead.

defaultScottyResponse :: ScottyResponse Source #

The default response has code 200 OK and empty body

newtype ActionT (m :: Type -> Type) a Source #

Constructors

ActionT 

Fields

Instances

Instances details
MonadTransControl ActionT Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Associated Types

type StT ActionT a 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

liftWith :: Monad m => (Run ActionT -> m a) -> ActionT m a #

restoreT :: Monad m => m (StT ActionT a) -> ActionT m a #

MonadTrans ActionT Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

lift :: Monad m => m a -> ActionT m a #

MonadBaseControl b m => MonadBaseControl b (ActionT m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

liftBaseWith :: (RunInBase (ActionT m) b -> b a) -> ActionT m a #

restoreM :: StM (ActionT m) a -> ActionT m a #

MonadReader r m => MonadReader r (ActionT m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

ask :: ActionT m r #

local :: (r -> r) -> ActionT m a -> ActionT m a #

reader :: (r -> a) -> ActionT m a #

MonadBase b m => MonadBase b (ActionT m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

liftBase :: b α -> ActionT m α #

MonadIO m => MonadFail (ActionT m) Source #

MonadFail instance for ActionT that converts fail calls into Scotty exceptions which allows these failures to be caught by Scotty's error handling system and properly returned as HTTP 500 responses. The instance throws a StringException containing both the failure message and a call stack for debugging purposes.

Instance details

Defined in Web.Scotty.Internal.Types

Methods

fail :: String -> ActionT m a #

MonadIO m => MonadIO (ActionT m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

liftIO :: IO a -> ActionT m a #

MonadUnliftIO m => Alternative (ActionT m) Source #

empty throws ActionError AENext, whereas (<|>) catches any ActionErrors or StatusErrors in the first action and proceeds to the second one.

Instance details

Defined in Web.Scotty.Internal.Types

Methods

empty :: ActionT m a #

(<|>) :: ActionT m a -> ActionT m a -> ActionT m a #

some :: ActionT m a -> ActionT m [a] #

many :: ActionT m a -> ActionT m [a] #

Applicative m => Applicative (ActionT m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

pure :: a -> ActionT m a #

(<*>) :: ActionT m (a -> b) -> ActionT m a -> ActionT m b #

liftA2 :: (a -> b -> c) -> ActionT m a -> ActionT m b -> ActionT m c #

(*>) :: ActionT m a -> ActionT m b -> ActionT m b #

(<*) :: ActionT m a -> ActionT m b -> ActionT m a #

Functor m => Functor (ActionT m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

fmap :: (a -> b) -> ActionT m a -> ActionT m b #

(<$) :: a -> ActionT m b -> ActionT m a #

Monad m => Monad (ActionT m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

(>>=) :: ActionT m a -> (a -> ActionT m b) -> ActionT m b #

(>>) :: ActionT m a -> ActionT m b -> ActionT m b #

return :: a -> ActionT m a #

MonadUnliftIO m => MonadPlus (ActionT m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

mzero :: ActionT m a #

mplus :: ActionT m a -> ActionT m a -> ActionT m a #

MonadCatch m => MonadCatch (ActionT m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

catch :: (HasCallStack, Exception e) => ActionT m a -> (e -> ActionT m a) -> ActionT m a #

MonadThrow m => MonadThrow (ActionT m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

throwM :: (HasCallStack, Exception e) => e -> ActionT m a #

MonadUnliftIO m => MonadUnliftIO (ActionT m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

withRunInIO :: ((forall a. ActionT m a -> IO a) -> IO b) -> ActionT m b #

(Monad m, Monoid a) => Monoid (ActionT m a) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

mempty :: ActionT m a #

mappend :: ActionT m a -> ActionT m a -> ActionT m a #

mconcat :: [ActionT m a] -> ActionT m a #

(Monad m, Semigroup a) => Semigroup (ActionT m a) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

(<>) :: ActionT m a -> ActionT m a -> ActionT m a #

sconcat :: NonEmpty (ActionT m a) -> ActionT m a #

stimes :: Integral b => b -> ActionT m a -> ActionT m a #

type StT ActionT a Source # 
Instance details

Defined in Web.Scotty.Internal.Types

type StM (ActionT m) a Source # 
Instance details

Defined in Web.Scotty.Internal.Types

type StM (ActionT m) a = StM (ReaderT ActionEnv m) a

withActionEnv :: forall (m :: Type -> Type) a. Monad m => (ActionEnv -> ActionEnv) -> ActionT m a -> ActionT m a Source #

tryAnyStatus :: MonadUnliftIO m => m a -> m Bool Source #

catches either ActionError (thrown by next), ScottyException (thrown if e.g. a query parameter is not found)

data RoutePattern Source #

Instances

Instances details
IsString RoutePattern Source # 
Instance details

Defined in Web.Scotty.Internal.Types