restful-snap-0.4.2
Safe HaskellNone
LanguageHaskell2010

Snap.Restful

Synopsis

Core API

addResource Source #

Arguments

:: HasHeist b 
=> Resource

Resource definition

-> [(CRUD, Handler b v ())]

Standard CRUD handlers

-> [(Text, Handler b v ())]

Additional resource level handlers

-> [(Text, Handler b v ())]

Additional instance/item level handlers

-> Snaplet (Heist b)

The Heist snaplet initialized in your app's Initializer

-> Initializer b v () 

One-stop convenience function to enable RESTful resources in your application. Call this function from your initializer passing it all of your resources and it will add the routes and splices for you.

addResourceRelative Source #

Arguments

:: HasHeist b 
=> Resource

Resource definition

-> [(CRUD, Handler b v ())]

Standard CRUD handlers

-> [(Text, Handler b v ())]

Additional resource level handlers

-> [(Text, Handler b v ())]

Additional instance/item level handlers

-> Snaplet (Heist b)

The Heist snaplet initialized in your app's Initializer

-> Initializer b v () 

Just like addResource, but makes the handlers relative to the current snaplet's root. Use this function if you're writing a snaplet.

initRest :: HasHeist b => Resource -> [(CRUD, Handler b () ())] -> [(Text, Handler b () ())] -> [(Text, Handler b () ())] -> Snaplet (Heist b) -> SnapletInit b () Source #

An initializer for encapsulating RESTful resources as a standalone snaplet.

Splice functions

resourceSplices :: Monad m => Resource -> Splices (HeistT n m Template) Source #

Paths at the resource/collection level

itemSplices :: Monad m => Resource -> DBId -> Splices (Splice m) Source #

Generates path splices for a resource item. These splices let you put resource links in your templates in DRY manner.

resourceCSplices :: MonadSnap m => Resource -> Splices (Splice m) Source #

Returns compiled splices for a resource.

itemCSplices :: Resource -> Splices (Maybe DBId -> Text) Source #

Generates compiled path splices for a resource item. These splices let you put resource links in your templates in DRY manner.

itemCSplice :: forall (n :: Type -> Type). MonadSnap n => Resource -> Splice n Source #

A splice that runs its children with all item splices for a resource. This function gets the id from the "id" param, which could have come in the request or might have been set up by a route capture string.

unitLens :: Lens' b () Source #

Since initRest returns unit, we provide a generic unit lens here for use with nestSnaplet in case you don't want to add a unit field to your application state type.

resourceRouter :: MonadSnap m => Resource -> [(CRUD, m a)] -> [(Text, m a)] -> [(Text, m a)] -> m a Source #

Generate a route handler for the routes returned by resourceRoutes. This function does add the rRoot prefix.

resourceRoutes :: MonadSnap m => Resource -> [(CRUD, m a)] -> [(Text, m a)] -> [(Text, m a)] -> [(ByteString, m a)] Source #

See addResource for an explanation of the arguments to this function. The routes returned ARE prefixed with rRoot from Resource.

Types

data CRUD Source #

Enumeration of all the different types of CRUD routes.

Constructors

RIndex

An item index

RShow

A single item

RNew

The form for creating a new item

REdit

The form for editing an item

RCreate

Create a new item

RUpdate

Update an item

RDestroy

Delete an item

Instances

Instances details
Eq CRUD Source # 
Instance details

Defined in Snap.Restful

Methods

(==) :: CRUD -> CRUD -> Bool #

(/=) :: CRUD -> CRUD -> Bool #

Ord CRUD Source # 
Instance details

Defined in Snap.Restful

Methods

compare :: CRUD -> CRUD -> Ordering #

(<) :: CRUD -> CRUD -> Bool #

(<=) :: CRUD -> CRUD -> Bool #

(>) :: CRUD -> CRUD -> Bool #

(>=) :: CRUD -> CRUD -> Bool #

max :: CRUD -> CRUD -> CRUD #

min :: CRUD -> CRUD -> CRUD #

Read CRUD Source # 
Instance details

Defined in Snap.Restful

Show CRUD Source # 
Instance details

Defined in Snap.Restful

Methods

showsPrec :: Int -> CRUD -> ShowS #

show :: CRUD -> String #

showList :: [CRUD] -> ShowS #

data Resource Source #

Encapsulates the data necessary to define a resource.

Constructors

Resource 

Fields

Instances

Instances details
Default Resource Source # 
Instance details

Defined in Snap.Restful

Methods

def :: Resource #

newtype DBId Source #

Constructors

DBId 

Fields

Instances

Instances details
Eq DBId Source # 
Instance details

Defined in Snap.Restful

Methods

(==) :: DBId -> DBId -> Bool #

(/=) :: DBId -> DBId -> Bool #

Num DBId Source # 
Instance details

Defined in Snap.Restful

Methods

(+) :: DBId -> DBId -> DBId #

(-) :: DBId -> DBId -> DBId #

(*) :: DBId -> DBId -> DBId #

negate :: DBId -> DBId #

abs :: DBId -> DBId #

signum :: DBId -> DBId #

fromInteger :: Integer -> DBId #

Ord DBId Source # 
Instance details

Defined in Snap.Restful

Methods

compare :: DBId -> DBId -> Ordering #

(<) :: DBId -> DBId -> Bool #

(<=) :: DBId -> DBId -> Bool #

(>) :: DBId -> DBId -> Bool #

(>=) :: DBId -> DBId -> Bool #

max :: DBId -> DBId -> DBId #

min :: DBId -> DBId -> DBId #

Read DBId Source # 
Instance details

Defined in Snap.Restful

Show DBId Source # 
Instance details

Defined in Snap.Restful

Methods

showsPrec :: Int -> DBId -> ShowS #

show :: DBId -> String #

showList :: [DBId] -> ShowS #

Default DBId Source # 
Instance details

Defined in Snap.Restful

Methods

def :: DBId #

Readable DBId Source # 
Instance details

Defined in Snap.Restful

Methods

fromText :: MonadPlus m => Text -> m DBId #

fromBS :: MonadPlus m => ByteString -> m DBId #

Generating forms and splices

class HasFormlet a where Source #

Type class for automatic formlet generation.

Methods

formlet :: Monad m => Formlet Text m a Source #

Instances

Instances details
HasFormlet Bool Source # 
Instance details

Defined in Snap.Restful

Methods

formlet :: forall (m :: Type -> Type). Monad m => Formlet Text m Bool Source #

HasFormlet Double Source # 
Instance details

Defined in Snap.Restful

Methods

formlet :: forall (m :: Type -> Type). Monad m => Formlet Text m Double Source #

HasFormlet Float Source # 
Instance details

Defined in Snap.Restful

Methods

formlet :: forall (m :: Type -> Type). Monad m => Formlet Text m Float Source #

HasFormlet Int Source # 
Instance details

Defined in Snap.Restful

Methods

formlet :: forall (m :: Type -> Type). Monad m => Formlet Text m Int Source #

HasFormlet Int8 Source # 
Instance details

Defined in Snap.Restful

Methods

formlet :: forall (m :: Type -> Type). Monad m => Formlet Text m Int8 Source #

HasFormlet Int16 Source # 
Instance details

Defined in Snap.Restful

Methods

formlet :: forall (m :: Type -> Type). Monad m => Formlet Text m Int16 Source #

HasFormlet Int32 Source # 
Instance details

Defined in Snap.Restful

Methods

formlet :: forall (m :: Type -> Type). Monad m => Formlet Text m Int32 Source #

HasFormlet Int64 Source # 
Instance details

Defined in Snap.Restful

Methods

formlet :: forall (m :: Type -> Type). Monad m => Formlet Text m Int64 Source #

HasFormlet Integer Source # 
Instance details

Defined in Snap.Restful

Methods

formlet :: forall (m :: Type -> Type). Monad m => Formlet Text m Integer Source #

HasFormlet Word8 Source # 
Instance details

Defined in Snap.Restful

Methods

formlet :: forall (m :: Type -> Type). Monad m => Formlet Text m Word8 Source #

HasFormlet Word16 Source # 
Instance details

Defined in Snap.Restful

Methods

formlet :: forall (m :: Type -> Type). Monad m => Formlet Text m Word16 Source #

HasFormlet Word32 Source # 
Instance details

Defined in Snap.Restful

Methods

formlet :: forall (m :: Type -> Type). Monad m => Formlet Text m Word32 Source #

HasFormlet Word64 Source # 
Instance details

Defined in Snap.Restful

Methods

formlet :: forall (m :: Type -> Type). Monad m => Formlet Text m Word64 Source #

HasFormlet String Source # 
Instance details

Defined in Snap.Restful

Methods

formlet :: forall (m :: Type -> Type). Monad m => Formlet Text m String Source #

HasFormlet ByteString Source # 
Instance details

Defined in Snap.Restful

Methods

formlet :: forall (m :: Type -> Type). Monad m => Formlet Text m ByteString Source #

HasFormlet Text Source # 
Instance details

Defined in Snap.Restful

Methods

formlet :: forall (m :: Type -> Type). Monad m => Formlet Text m Text Source #

class PrimSplice a where Source #

Type class for automatic splice generation.

Methods

iPrimSplice :: Monad m => a -> m [Node] Source #

cPrimSplice :: a -> Builder Source #

Instances

Instances details
PrimSplice Bool Source # 
Instance details

Defined in Snap.Restful

PrimSplice Double Source # 
Instance details

Defined in Snap.Restful

PrimSplice Float Source # 
Instance details

Defined in Snap.Restful

PrimSplice Int Source # 
Instance details

Defined in Snap.Restful

PrimSplice Int8 Source # 
Instance details

Defined in Snap.Restful

PrimSplice Int16 Source # 
Instance details

Defined in Snap.Restful

PrimSplice Int32 Source # 
Instance details

Defined in Snap.Restful

PrimSplice Int64 Source # 
Instance details

Defined in Snap.Restful

PrimSplice Integer Source # 
Instance details

Defined in Snap.Restful

PrimSplice Word8 Source # 
Instance details

Defined in Snap.Restful

PrimSplice Word16 Source # 
Instance details

Defined in Snap.Restful

PrimSplice Word32 Source # 
Instance details

Defined in Snap.Restful

PrimSplice Word64 Source # 
Instance details

Defined in Snap.Restful

PrimSplice String Source # 
Instance details

Defined in Snap.Restful

PrimSplice Text Source # 
Instance details

Defined in Snap.Restful

PrimSplice UTCTime Source # 
Instance details

Defined in Snap.Restful

PrimSplice Day Source # 
Instance details

Defined in Snap.Restful

PrimSplice a => PrimSplice (Maybe a) Source # 
Instance details

Defined in Snap.Restful

iPrimText :: Monad m => Text -> m [Node] Source #

iPrimShow :: (Monad m, Show a) => a -> m [Node] Source #

Functions for generating paths

indexPath :: Resource -> Text Source #

Generates the path for the resource index.

createPath :: Resource -> Text Source #

Generates the path for creating a resource.

showPath :: Resource -> DBId -> Text Source #

Generates the path for showing a single resource item.

newPath :: Resource -> Text Source #

Generates the path for a form to a new resource.

editPath :: Resource -> DBId -> Text Source #

Generates the path for a form to a new resource.

updatePath :: Resource -> DBId -> Text Source #

Generates the path for updating a single resource item.

destroyPath :: Resource -> DBId -> Text Source #

Generates the path for deleting a resource item.

itemActionPath :: Resource -> Text -> DBId -> Text Source #

Generates a path for an item action.

templatePath :: Resource -> CRUD -> ByteString Source #

Return heist template location for given crud action

Misc helpers

redirToItem :: MonadSnap m => Resource -> DBId -> m a Source #

Redirect to given item's default show page

setFormAction :: MonadSnap m => Text -> m a -> m a Source #

Sets the RESTFormAction param.

getFormAction :: MonadSnap m => HeistT n m [Node] Source #

Gets the RESTFormAction param.