scotty-0.11.5: 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.

Instances
Default Options Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

def :: Options #

data ScottyState e m Source #

Constructors

ScottyState 
Instances
Default (ScottyState e m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

def :: ScottyState e m #

newtype ScottyT e m a Source #

Constructors

ScottyT 

Fields

Instances
Monad (ScottyT e m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

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

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

return :: a -> ScottyT e m a #

fail :: String -> ScottyT e m a #

Functor (ScottyT e m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

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

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

Applicative (ScottyT e m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

pure :: a -> ScottyT e m a #

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

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

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

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

data ActionError e Source #

Constructors

Redirect Text 
Next 
Finish 
ActionError e 
Instances
ScottyError e => ScottyError (ActionError e) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

(ScottyError e, Monad m) => MonadError (ActionError e) (ActionT e m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

throwError :: ActionError e -> ActionT e m a #

catchError :: ActionT e m a -> (ActionError e -> ActionT e m a) -> ActionT e m a #

class ScottyError e where Source #

In order to use a custom exception type (aside from Text), you must define an instance of ScottyError for that type.

type ErrorHandler e m = Maybe (e -> ActionT e m ()) Source #

type Param = (Text, Text) Source #

data ScottyResponse Source #

Constructors

SR 
Instances
Default ScottyResponse Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

def :: ScottyResponse #

newtype ActionT e m a Source #

Instances
(MonadBase b m, ScottyError e) => MonadBase b (ActionT e m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

liftBase :: b α -> ActionT e m α #

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

Defined in Web.Scotty.Internal.Types

Associated Types

type StM (ActionT e m) a :: Type #

Methods

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

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

MonadTrans (ActionT e) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

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

MonadTransControl (ActionT e) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Associated Types

type StT (ActionT e) a :: Type #

Methods

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

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

(ScottyError e, Monad m) => MonadError (ActionError e) (ActionT e m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

throwError :: ActionError e -> ActionT e m a #

catchError :: ActionT e m a -> (ActionError e -> ActionT e m a) -> ActionT e m a #

(Monad m, ScottyError e) => Monad (ActionT e m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

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

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

return :: a -> ActionT e m a #

fail :: String -> ActionT e m a #

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

Defined in Web.Scotty.Internal.Types

Methods

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

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

(Monad m, ScottyError e) => MonadFail (ActionT e m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

fail :: String -> ActionT e m a #

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

Defined in Web.Scotty.Internal.Types

Methods

pure :: a -> ActionT e m a #

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

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

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

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

(Monad m, ScottyError e) => Alternative (ActionT e m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

empty :: ActionT e m a #

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

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

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

(Monad m, ScottyError e) => MonadPlus (ActionT e m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

mzero :: ActionT e m a #

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

(MonadIO m, ScottyError e) => MonadIO (ActionT e m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

liftIO :: IO a -> ActionT e m a #

(MonadThrow m, ScottyError e) => MonadThrow (ActionT e m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

throwM :: Exception e0 => e0 -> ActionT e m a #

(MonadCatch m, ScottyError e) => MonadCatch (ActionT e m) Source # 
Instance details

Defined in Web.Scotty.Internal.Types

Methods

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

type StT (ActionT e) a Source # 
Instance details

Defined in Web.Scotty.Internal.Types

type StM (ActionT e m) a Source # 
Instance details

Defined in Web.Scotty.Internal.Types

type StM (ActionT e m) a = ComposeSt (ActionT e) m a