yesod-vend-0.1: Simple CRUD classes for easy view creation for Yesod

Portabilityportable
Stabilityexperimental
MaintainerKrzysztof Skrzętnicki <gtener@gmail.com>
Safe HaskellSafe-Infered

Yesod.VEND

Contents

Description

This module provides simple typeclass CRUD which implements CRUD (or VEND: View Edit New Delete) functionality for Yesod.

There are default implementations that are unfortunately filtered out by Haddock. The implementation uses DefaultSignatures extension to not force a specific implementation on a library user.

An example is given below.

Suppose we have a User entity defined as config/models:

 User
     ident Text
     name Text Maybe
     address Text Maybe
     telephone Text Maybe

Our module would then start with:

 {-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
 module Handler.User where
  
 import Import
 import Yesod.VEND
  
 import Data.Maybe

Define helper datatype.

 data UserP = UserP

Provide routing. This assumes that config/routes reads:

 /user/new                    UserNewR    
 /user/edit/#UserId           UserEditR   
 /user/delete/#UserId         UserDeleteR 
 /user/view/all               UserViewAllR   
 /user/view/single/#UserId    UserViewR   

Methods:

 handleUserNewR = newR UserP
 handleUserDeleteR = deleteR UserP
 handleUserEditR = editR UserP
 handleUserViewR = viewR UserP
 handleUserViewAllR = viewAllR UserP

Define EntityDeep instance for UserId. We use default implementations.

 instance EntityDeep UserId where
     type EntT UserId = User
     type FullEntT UserId = User

Define CRUD instance for our helper type UserP. Define ValT and KeyT types.

 instance CRUD UserP where
     type ValT UserP = User
     type KeyT UserP = UserId
  

Wire routing information in:

     newRt _ = UserNewR
     editRt _ = UserEditR
     deleteRt _ = UserDeleteR
     viewRt _ = UserViewR
     viewAllRt _ = UserViewAllR
  

Define which parameters will be displayed for entity and how:

     params _ = [(EntityParam "Ident" userIdent id markupToWidget)
                ,(EntityParam "Name" userName mns mnsw)
                ,(EntityParam "Address" userAddress mns mnsw)
                ,(EntityParam "Telephone" userTelephone mns mnsw)
                ] where mns = fromMaybe "not set"
                        mnsw = maybe [whamlet|<i>not set</i>|] markupToWidget
  

Specify sorting in 'view all' view:

     viewAllOptions _ = [Asc UserId]
  

Define entity name:

     entName _ = "User"

Form for creating/editing entity:

     form _ proto = return $ renderDivs $  
                     User
                       <$> areq textField "Identifier" (fmap userIdent proto)
                       <*> aopt textField "Name" (fmap userName proto)
                       <*> aopt textField "Address" (fmap userAddress proto)
                       <*> aopt textField "Telephone" (fmap userTelephone proto)

Synopsis

Documentation

data EntityParam master sub a Source

Datatype for providing different views on specific datatype. Transforms the parameter into intermediate datatype b from which one can use epToText to get Text or epToWidget to get a GWidget.

Constructors

forall b . EntityParam 

Fields

epName :: Text
 
epGet :: a -> b
 
epToText :: b -> Text
 
epToWidget :: b -> GWidget master sub ()
 

Helpers to work around problems with existential types.

epGetText :: EntityParam t t1 t2 -> t2 -> TextSource

We cannot use record syntax to access fields of existential types. Instead we have:

  epGetText (EntityParam _ pGet pToText _) = pToText . pGet

epGetWidget :: EntityParam t t1 t2 -> t2 -> GWidget t t1 ()Source

We cannot use record syntax to access fields of existential types. Instead we have:

 epGetWidget (EntityParam _ pGet _ pToWidget) = pToWidget . pGet

class EntityDeep a whereSource

Class for accessing entities referenced by a entity type. For example for entities Foo, Bar:

 Foo
     name Text
 Bar
     size Int
     foo  FooId

We would have this for Bar:

 instance EntityDeep BarId where
     type EntT = Bar
     type FullEntT = (Bar,Foo)
  
     get404Full key = runDB $ do
                    v1 <- get404 key
                    v2 <- get404 (barFoo v1)
                    return (v1,v2)
  
     entityCore _ = fst
     paramsFull _ = [(EntityParam "Size" (barSize . fst) id markupToWidget)
                    ,(EntityParam "Foo's name" (fooName . snd) id markupToWidget)]
       

Associated Types

type EntT a :: *Source

base entity type. Not critically needed but useful.

type FullEntT a :: *Source

full entity type.

Methods

get404Full :: a -> GHandler master sub (FullEntT a)Source

get full entity from base. default implementation works akin to get404.

entityCore :: a -> FullEntT a -> EntT aSource

return base type from full type

paramsFull :: a -> [EntityParam master sub (FullEntT a)]Source

get a list of parameters describing the full type

displayEntityWidget :: a -> [EntityParam master sub a] -> Bool -> GWidget master sub ()Source

Given description of entity parameters (EntityParam list) and terse/not terse option return a widget displaying the entity.

class EntityDeep (KeyT a) => CRUD a whereSource

Core typeclass of this package. Default implementations of handlers use other methods to provide sensible default views. They can be all overriden if needed.

Associated Types

type ValT a Source

entity value type

type KeyT a Source

entity key type

Methods

getSomeKey :: a -> KeyT aSource

provide a value of type 'KeyT a'. Default implementation is undefined.

getSomeVal :: a -> ValT aSource

provide a value of type 'ValT a'. Default implementation is undefined.

viewAllOptions :: a -> [SelectOpt (ValT a)]Source

used for sorting entities in 'view all'

newRt :: a -> Route siteSource

route to 'new element'

viewAllRt :: a -> Route siteSource

route to 'view all elements'

viewRt :: a -> KeyT a -> Route siteSource

route to 'view element'

deleteRt :: a -> KeyT a -> Route siteSource

route to 'delete element'

editRt :: a -> KeyT a -> Route siteSource

route to 'edit element'

displayWidget :: a -> ValT a -> Bool -> GWidget master sub ()Source

provide widget for displaying an element. Bool argument specifies if this is for "terse" view or not.

displayHeaderWidget :: a -> Bool -> GWidget master sub ()Source

provide widget for displaying element header. Used in 'view all'.

params :: a -> [EntityParam master sub (ValT a)]Source

simple version of paramsFull only for ValT type.

entName :: a -> TextSource

entity name. this will be changed in future versions to support proper internationalization.

form :: a -> Maybe (ValT a) -> GHandler master sub (Html -> MForm master sub (FormResult (ValT a), GWidget master sub ()))Source

form for creating new entity/editing old one.

dForm :: a -> GHandler master sub (Html -> MForm master sub (FormResult Bool, GWidget master sub ()))Source

deletion form.

viewR :: a -> KeyT a -> GHandler master sub RepHtmlSource

handler for viewRt

editR :: a -> KeyT a -> GHandler master sub RepHtmlSource

handler for editRt

newR :: a -> GHandler master sub RepHtmlSource

handler for newRt

deleteR :: a -> KeyT a -> GHandler master sub RepHtmlSource

handler for deleteRt

viewAllR :: a -> GHandler master sub RepHtmlSource

handler for viewAllRt

Utility functions

getTerse :: GHandler master sub BoolSource

Check if the view should be "terse" or not. Checks for "terse" in GET parameters. Default is True. 1 means True, 0 means False.

markupToWidget :: ToMarkup a => a -> GWidget sub master ()Source

make GWidget from any type that implements ToMarkup