Spock-core-0.13.0.0: Another Haskell web framework for rapid development

Safe HaskellNone
LanguageHaskell98

Web.Spock.Core

Contents

Synopsis

Lauching Spock

runSpock :: Port -> IO Middleware -> IO () Source #

Run a Spock application. Basically just a wrapper around run.

runSpockNoBanner :: Port -> IO Middleware -> IO () Source #

Like runSpock, but does not display the banner "Spock is running on port XXX" on stdout.

spockAsApp :: IO Middleware -> IO Application Source #

Convert a middleware to an application. All failing requests will result in a 404 page

Spock's route definition monad

spockT :: MonadIO m => (forall a. m a -> IO a) -> SpockT m () -> IO Middleware Source #

Create a raw spock application with custom underlying monad Use runSpock to run the app or spockAsApp to create a Wai.Application The first argument is request size limit in bytes. Set to Nothing to disable.

spockConfigT :: forall m. MonadIO m => SpockConfig -> (forall a. m a -> IO a) -> SpockT m () -> IO Middleware Source #

Like spockT, but with additional configuration for request size and error handlers passed as first parameter.

data SpockCtxT ctx m a Source #

Instances

RouteM SpockCtxT Source # 

Methods

addMiddleware :: Monad m => Middleware -> SpockCtxT ctx m () Source #

withPrehook :: MonadIO m => ActionCtxT ctx m ctx' -> SpockCtxT ctx' m () -> SpockCtxT ctx m () Source #

wireAny :: Monad m => SpockMethod -> ([Text] -> ActionCtxT ctx m ()) -> SpockCtxT ctx m () Source #

wireRoute :: (Monad m, HasRep xs) => SpockMethod -> Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> SpockCtxT ctx m () Source #

MonadTrans (SpockCtxT ctx) Source # 

Methods

lift :: Monad m => m a -> SpockCtxT ctx m a #

Monad m => Monad (SpockCtxT ctx m) Source # 

Methods

(>>=) :: SpockCtxT ctx m a -> (a -> SpockCtxT ctx m b) -> SpockCtxT ctx m b #

(>>) :: SpockCtxT ctx m a -> SpockCtxT ctx m b -> SpockCtxT ctx m b #

return :: a -> SpockCtxT ctx m a #

fail :: String -> SpockCtxT ctx m a #

Functor m => Functor (SpockCtxT ctx m) Source # 

Methods

fmap :: (a -> b) -> SpockCtxT ctx m a -> SpockCtxT ctx m b #

(<$) :: a -> SpockCtxT ctx m b -> SpockCtxT ctx m a #

Monad m => Applicative (SpockCtxT ctx m) Source # 

Methods

pure :: a -> SpockCtxT ctx m a #

(<*>) :: SpockCtxT ctx m (a -> b) -> SpockCtxT ctx m a -> SpockCtxT ctx m b #

liftA2 :: (a -> b -> c) -> SpockCtxT ctx m a -> SpockCtxT ctx m b -> SpockCtxT ctx m c #

(*>) :: SpockCtxT ctx m a -> SpockCtxT ctx m b -> SpockCtxT ctx m b #

(<*) :: SpockCtxT ctx m a -> SpockCtxT ctx m b -> SpockCtxT ctx m a #

MonadIO m => MonadIO (SpockCtxT ctx m) Source # 

Methods

liftIO :: IO a -> SpockCtxT ctx m a #

Defining routes

data Path (as :: [*]) (pathState :: PathState) :: [*] -> PathState -> * #

Instances

((~) [*] a ([] *), (~) PathState pathState Open) => IsString (Path a pathState) 

Methods

fromString :: String -> Path a pathState #

root :: Path ([] *) Open #

The root of a path piece. Use to define a handler for "/"

type Var a = Path ((:) * a ([] *)) Open #

var :: (Typeable * a, FromHttpApiData a) => Path ((:) * a ([] *)) Open #

A route parameter

static :: String -> Path ([] *) Open #

A static route piece

(<//>) :: Path as Open -> Path bs ps -> Path (Append as bs) ps Source #

Combine two path components

wildcard :: Path ((:) * Text ([] *)) Closed #

Matches the rest of the route. Should be the last part of the path.

Rendering routes

renderRoute :: AllHave ToHttpApiData as => Path as Open -> HVectElim as Text Source #

Render a route applying path pieces

Hooking routes

prehook :: (RouteM t, MonadIO m) => ActionCtxT ctx m ctx' -> t ctx' m () -> t ctx m () Source #

Specify an action that will be run before all subroutes. It can modify the requests current context

get :: (HasRep xs, RouteM t, Monad m) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #

Specify an action that will be run when the HTTP verb GET and the given route match

post :: (HasRep xs, RouteM t, Monad m) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #

Specify an action that will be run when the HTTP verb POST and the given route match

getpost :: (HasRep xs, RouteM t, Monad m, Monad (t ctx m)) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #

Specify an action that will be run when the HTTP verb 'GET'/'POST' and the given route match

head :: (HasRep xs, RouteM t, Monad m) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #

Specify an action that will be run when the HTTP verb HEAD and the given route match

put :: (HasRep xs, RouteM t, Monad m) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #

Specify an action that will be run when the HTTP verb PUT and the given route match

delete :: (HasRep xs, RouteM t, Monad m) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #

Specify an action that will be run when the HTTP verb DELETE and the given route match

patch :: (HasRep xs, RouteM t, Monad m) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #

Specify an action that will be run when the HTTP verb PATCH and the given route match

hookRoute :: (HasRep xs, RouteM t, Monad m) => StdMethod -> Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #

Specify an action that will be run when a standard HTTP verb and the given route match

hookRouteCustom :: (HasRep xs, RouteM t, Monad m) => Text -> Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #

Specify an action that will be run when a custom HTTP verb and the given route match

hookAny :: (RouteM t, Monad m) => StdMethod -> ([Text] -> ActionCtxT ctx m ()) -> t ctx m () Source #

Specify an action that will be run when a standard HTTP verb matches but no defined route matches. The full path is passed as an argument

hookAnyCustom :: (RouteM t, Monad m) => Text -> ([Text] -> ActionCtxT ctx m ()) -> t ctx m () Source #

Specify an action that will be run when a custom HTTP verb matches but no defined route matches. The full path is passed as an argument

hookRouteAll :: (HasRep xs, RouteM t, Monad m) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #

Specify an action that will be run regardless of the HTTP verb

hookAnyAll :: (RouteM t, Monad m) => ([Text] -> ActionCtxT ctx m ()) -> t ctx m () Source #

Specify an action that will be run regardless of the HTTP verb and no defined route matches. The full path is passed as an argument

data StdMethod :: * #

HTTP standard method (as defined by RFC 2616, and PATCH which is defined by RFC 5789).

Constructors

GET 
POST 
HEAD 
PUT 
DELETE 
TRACE 
CONNECT 
OPTIONS 
PATCH 

Adding Wai.Middleware

middleware :: (RouteM t, Monad m) => Middleware -> t ctx m () Source #

Hook wai middleware into Spock

Actions

Config

data SpockConfig Source #

Constructors

SpockConfig 

Fields

defaultSpockConfig :: SpockConfig Source #

Default Spock configuration. No restriction on maximum request size; error handler simply prints status message as plain text and all errors are logged to stderr.

Internals

hookRoute' :: (HasRep xs, RouteM t, Monad m) => SpockMethod -> Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #

Specify an action that will be run when a HTTP verb and the given route match

hookAny' :: (RouteM t, Monad m) => SpockMethod -> ([Text] -> ActionCtxT ctx m ()) -> t ctx m () Source #

Specify an action that will be run when a HTTP verb matches but no defined route matches. The full path is passed as an argument

data SpockMethod Source #

The SpockMethod allows safe use of http verbs via the MethodStandard constructor and StdMethod, and custom verbs via the MethodCustom constructor.

Constructors

MethodStandard !HttpMethod

Standard HTTP Verbs from StdMethod

MethodCustom !Text

Custom HTTP Verbs using Text

MethodAny

Match any HTTP verb

Instances

Eq SpockMethod Source # 
Generic SpockMethod Source # 

Associated Types

type Rep SpockMethod :: * -> * #

Hashable SpockMethod Source # 
type Rep SpockMethod Source # 
type Rep SpockMethod = D1 * (MetaData "SpockMethod" "Web.Spock.Internal.Wire" "Spock-core-0.13.0.0-HLqSHqwRtFy47IHokh2N7G" False) ((:+:) * (C1 * (MetaCons "MethodStandard" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HttpMethod))) ((:+:) * (C1 * (MetaCons "MethodCustom" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) (C1 * (MetaCons "MethodAny" PrefixI False) (U1 *))))