yesod-crud-0.1.3: Generic administrative CRUD operations as a Yesod subsite

Copyright©2015 Christopher League
Maintainerleague@contrapunctus.net
Safe HaskellNone
LanguageHaskell2010

Yesod.Contrib.League.Crud

Contents

Description

This package helps you build administrative CRUD operations (Create, Retrieve, Update, Delete) into your web site, as Yesod subsites. There is a demo site in the example directory in the distribution.

To begin, add subsites to your routes file, like these:

/users         UserCrudR  CrudSubsite-UserCrud  mkUserCrud
/pubs/#UserId  PubCrudR   CrudSubsite-PubCrud   mkPubCrud

Now, in your Foundation module, you must define the subsite foundation types and functions. Here we have one foundation type that is nullary, and another that carries a piece of data.

data UserCrud = UserCrud
mkUserCrud :: a -> CrudSubsite UserCrud
mkUserCrud _ = CrudSubsite UserCrud

data PubCrud = PubCrud UserId
mkPubCrud :: a -> UserId -> CrudSubsite PubCrud
mkPubCrud _ = CrudSubsite . PubCrud

Next, define the type families on which these will operate. The simplest case is that ObjId is a Persistent database Key and Obj is one of your model types, but yesod-crud supports other types and non-Persistent databases too.

instance CrudTypes UserCrud where
  type Site UserCrud = App
  type ObjId UserCrud = UserId
  type Obj UserCrud = User

instance CrudTypes PubCrud where
  type Site PubCrud = App
  type ObjId PubCrud = PublicationId
  type Obj PubCrud = Publication

The above generally must go within the Foundation.hs of a scaffolded site, because it relies on the App type, and is in turn used in the routes file. The remaining CRUD operations can be defined elsewhere and then imported into Application.hs for the dispatcher to access.

instance RenderMessage (CrudSubsite UserCrud) CrudMessage where
  renderMessage _ _ CrudMsgEntity = "User"
  renderMessage _ _ CrudMsgEntities = "Users"
  renderMessage _ _ m = defaultCrudMessage m

instance Crud UserCrud where
  crudDB = return crudPersistDefaults
  crudShow = return . userIdent
  crudEq u v = return $ u == v
  crudMakeForm uOpt =
    return $ renderDivs $ User
    <$> areq textField "User name" (userIdent <$> uOpt)
    <*> aopt passwordField "Password" (userPassword <$> uOpt)

The minimal definition above will provide pages to list users, add a new user, update existing users, and delete users (with a confirmation step). Various aspects of the look and functionality can be overridden, and the CRUD widgets can be mixed and matched on other pages too.

Comments and critiques are welcome. Please use the Issues feature at https://github.com/league/yesod-crud

Synopsis

Types

class (Eq (ObjId sub), PathPiece (ObjId sub)) => CrudTypes sub Source

Define the types used by your CRUD subsite.

Associated Types

type Site sub :: * Source

The site's foundation type

type ObjId sub :: * Source

The type of primary keys to your objects

type Obj sub :: * Source

The type of the objects themselves

newtype CrudSubsite sub Source

The foundation type for a CRUD subsite, wrapped around your own type sub that determines the entity and carries any contextual data from the route.

Constructors

CrudSubsite 

Fields

unCrud :: sub
 

Instances

Eq (ObjId sub) => Eq (Route (CrudSubsite sub)) 
Read (ObjId sub) => Read (Route (CrudSubsite sub)) 
Show (ObjId sub) => Show (Route (CrudSubsite sub)) 
CrudTypes sub => RenderRoute (CrudSubsite sub) 
CrudTypes sub => ParseRoute (CrudSubsite sub) 
(Crud sub, (~) * (Site sub) site) => YesodSubDispatch (CrudSubsite sub) (HandlerT site IO) 
data Route (CrudSubsite sub)  

type CrudHandler sub = HandlerT (CrudSubsite sub) (SiteHandler sub) Source

The type of a subsite handler.

type SiteHandler sub = HandlerT (Site sub) IO Source

The type of the (parent) site handler.

type CrudWidget sub = WidgetT (Site sub) IO () Source

Widgets are relative to the parent site, not the subsite. This makes it a little more convenient to use messages and routes from the parent.

type CrudForm sub = Html -> MForm (SiteHandler sub) (FormResult (Obj sub), CrudWidget sub) Source

Forms are also defined relative to the parent site.

Database operations

type Ent sub = (ObjId sub, Obj sub) Source

Like the Persistent Entity type, but just a simple pair.

data CrudDB sub Source

The required database operations are packaged into this record type. This makes it straightforward to inherit the operations wholesale into different CRUD subsites (whether you are using Persistent or another mechanism), but they can still be overridden by the similarly-named methods in the Crud class.

Constructors

CrudDB 

Fields

crudSelect' :: CrudM sub [Ent sub]
 
crudInsert' :: Obj sub -> CrudM sub (ObjId sub)
 
crudGet' :: ObjId sub -> CrudM sub (Maybe (Obj sub))
 
crudReplace' :: ObjId sub -> Obj sub -> CrudM sub ()
 
crudDelete' :: ObjId sub -> CrudM sub ()
 

CRUD operations and handlers

class (CrudTypes sub, Yesod (Site sub), RenderMessage (Site sub) FormMessage, RenderMessage (CrudSubsite sub) CrudMessage) => Crud sub where Source

All the necessary CRUD handlers and operations are defined in this class, and can be overridden as necessary for each CRUD subsite.

Minimal complete definition

crudDB, crudShow, crudEq, crudMakeForm

Methods

crudDB :: CrudM sub (CrudDB sub) Source

Returns a record of database operations, for use by the next several methods. You can inherit operations wholesale by defining this method, and then override others. (If you override all the other DB methods, then this one should never be used.)

crudSelect :: CrudM sub [Ent sub] Source

Retrieve a set of entities from the database, paired with their ObjId keys.

crudInsert :: Obj sub -> CrudM sub (ObjId sub) Source

Insert a new object into the database, returning its key.

crudGet :: ObjId sub -> CrudM sub (Maybe (Obj sub)) Source

Retrieve an object with the given key.

crudReplace :: ObjId sub -> Obj sub -> CrudM sub () Source

Replace the object at the given key with a modified one.

crudDelete :: ObjId sub -> CrudM sub () Source

Remove the object with the given key.

crudShow :: Obj sub -> CrudM sub Text Source

Produce a small chunk of text to describe the given object. This is used in the default crudListWidget, and various other places that name the object, such as the alert message "Created raspberry swirl donut." We don't require that object types implement Show, but if yours does this could be as simple as:

crudShow = return . tshow

crudShowHtml :: Obj sub -> CrudM sub Html Source

This is a variant of crudShow that allows HTML, not just text. It is used only in crudListWidget, and by default it just uses crudShow. Override it if you're using the default crudListWidget but you want markup in your object descriptions.

crudEq :: Obj sub -> Obj sub -> CrudM sub Bool Source

When an update form is submitted, we check (in postCrudUpdateR) whether any changes were made before sending it to the database. If you'd like to update it regardless, return False. Be careful with forms that fill in a "last updated" field, because it should be ignored in determining equality. To use an Eq instance:

crudEq u v = return $ u == v

crudMakeForm Source

Arguments

:: Maybe (Obj sub)

The object to update, or Nothing if creating

-> CrudM sub (CrudForm sub) 

Produce a form to create or update an object.

crudNextPage Source

Arguments

:: Maybe (ObjId sub)

The object that was saved, or Nothing if deleted

-> CrudM sub (Route (Site sub)) 

After creating, updating, or deleting, what page should we transition to? The default implementation returns to the list page CrudListR. If you have a "view" page outside of the CRUD subsite, you could go there, based on the ObjId parameter. (The result is a global site route, not limited to the subsite. Use getRouter to translate local CRUD routes.)

crudAlert Source

Arguments

:: Route (CrudSubsite sub)

The page that we just completed

-> Either SomeException (Obj sub)

The result of that operation

-> CrudM sub () 

This method sets an alert/flash message to appear at the top of the next page. By default, it uses defaultCrudAlertMessage and setMessage. Override it if you have a different messaging system. The result parameter will be Right if the current page completed successfully. It contains the object, even for objects that were deleted.

crudListWidget :: CrudM sub (CrudWidget sub) Source

Creates a list widget, not including its title. The default implementation uses an ordered list, the crudShowHtml description, and simple text hyperlinks to update, delete, and create a new object. Override it to substitute a table or icons. This widget should not include a title, which will be added by getCrudListR. (But you can embed a list widget in any other handler too.)

crudFormWidget :: Route (CrudSubsite sub) -> (CrudWidget sub, Enctype) -> CrudM sub (CrudWidget sub) Source

Creates a widget that wraps a rendered form in a form tag and adds the submit button. Override it to customize the tag or button.

crudCreateWidget :: CrudM sub (CrudWidget sub) Source

Creates a widget containing the object creation form. You can embed this in the list widget (replacing the text link) or in any other handler. All the real work is done by crudMakeForm, generateFormPost, and crudFormWidget, so there's probably no need to override this method itself.

crudViewWidget :: Ent sub -> CrudM sub (CrudWidget sub) Source

View entity details

crudDeleteWidget :: Ent sub -> CrudM sub (CrudWidget sub) Source

Creates a widget to confirm deletion of an object. Override this if you want to have a more sophisticated confirmation warning (such as showing what other entities would be affected) or to change the delete button.

crudFormLayout :: Route (CrudSubsite sub) -> (CrudWidget sub, Enctype) -> CrudM sub Html Source

Create a form widget using crudFormWidget, and then add the title and convert to HTML using crudLayout. Probably no need to override this method, unless to customize the default title based on CrudMsgEntity.

crudLayout :: CrudWidget sub -> CrudM sub Html Source

Convert a CRUD widget to HTML. Default implementation simply uses defaultLayout.

getCrudListR :: CrudHandler sub TypedContent Source

Handler for GET on the list route CrudListR, to display a list of all objects. Primarily uses crudListWidget and crudLayout, but also sets a title based on CrudMsgEntities.

getCrudCreateR :: CrudHandler sub TypedContent Source

Handler for GET on the creation form CrudCreateR, to display an empty form. Primarily uses crudMakeForm and crudFormLayout.

postCrudCreateR :: CrudHandler sub TypedContent Source

Handler for POST on CrudCreateR, to create a new object. On success, it inserts the object and displays an alert on the next page. If the form validation fails, it displays the form again with errors. (If the database insertion itself fails, it still moves on to the next page and displays the exception as an alert.)

getCrudViewR :: ObjId sub -> CrudHandler sub TypedContent Source

Handler for GET on CrudViewR, an object's details request. It displays the object and employs an empty Yesod form for return.

getCrudDeleteR :: ObjId sub -> CrudHandler sub TypedContent Source

Handler for GET on CrudDeleteR, a deletion request. It displays the object and employs an empty Yesod form for its CSRF token.

postCrudDeleteR :: ObjId sub -> CrudHandler sub TypedContent Source

Handler for POST on CrudDeleteR, confirming a deletion request. It displays the result as an alert on the next page.

getCrudUpdateR :: ObjId sub -> CrudHandler sub TypedContent Source

Handler for GET on CrudUpdateR, to display a form filled out with an existing object. Most of the work is done by crudGet, crudMakeForm, and crudFormLayout.

postCrudUpdateR :: ObjId sub -> CrudHandler sub TypedContent Source

Handler for POST on CrudUpdateR, to update an object. Guards against updating an object that has not been changed, as detected by crudEq. If the form validation fails, it displays the form again with errors. (If the database update itself fails, it still moves on to the next page and displays the exception as an alert.)

The custom monad

data CrudM sub a Source

A custom monad that can run either in the site or subsite handler. It carries the subsite foundation object (retrieved with getCrud) and appropriate converters for routes (getRouter) and messages (getMessenger).

Instances

MonadBaseControl IO (CrudM sub) 
MonadBase IO (CrudM sub) 
Monad (CrudM sub) 
Functor (CrudM sub) 
Applicative (CrudM sub) 
MonadIO (CrudM sub) 
MonadThrow (CrudM sub) 
MonadLogger (CrudM sub) 
MonadResource (CrudM sub) 
MonadHandler (CrudM sub) 
type HandlerSite (CrudM sub) = Site sub 
type StM (CrudM sub) a = a 

getCrud :: CrudM sub sub Source

Retrieve the value of the foundation type. This is needed if your CRUD paths contain parameters, such as /customer/31/donut/15/update. The 31 is stored in the foundation, and the 15 in the subsite route.

runCrudSubsite Source

Arguments

:: RenderMessage (CrudSubsite sub) CrudMessage 
=> CrudM sub a

Action to run

-> CrudHandler sub a 

Run a CrudM action within the subsite handler.

runCrudSite Source

Arguments

:: RenderMessage (CrudSubsite sub) CrudMessage 
=> sub

Foundation value

-> (Route (CrudSubsite sub) -> Route (Site sub))

Translate subsite route to parent

-> CrudM sub a

Action to run

-> SiteHandler sub a 

Run a CrudM action within the global site handler. You must provide the foundation value and a route translator.

Messages

data CrudMessage Source

All titles, links, alerts, and button labels emitted by the default implementations of Crud operations are represented by constructors of this type. See defaultCrudMessage for basic conversion to English text. When you implement RenderMessage for this type, consider overriding at least the first two or three constructors to customize your entity name:

instance RenderMessage (CrudSubsite DonutCrud) CrudMessage where
  renderMessage _ _ CrudMsgEntity = "Donut"
  renderMessage _ _ CrudMsgEntities = "Donuts"
  renderMessage _ _ CrudMsgNoEntities = "Sorry, there are no more donuts."
  renderMessage _ _ m = defaultCrudMessage m

Constructors

CrudMsgEntity

The singular name for your entity

CrudMsgEntities

The plural name for your entity

CrudMsgNoEntities

Message when no entities are found

CrudMsgAlertCreated Text

The message "Created [object]"

CrudMsgAlertDeleted Text

The message "Deleted [object]"

CrudMsgAlertNoChanges Text

The message "No changes to [object]"

CrudMsgAlertUpdated Text

The message "Updated [object]"

CrudMsgButtonDelete

The label on button to confirm delete

CrudMsgButtonSubmit

The label on button to save/submit

CrudMsgConfirmDelete Text

The message "Really delete [object]?"

CrudMsgLinkCreate

The link text leading to the create page

CrudMsgLinkDelete

The link text leading to the delete page

CrudMsgLinkUpdate

The link text leading to the update form

CrudMsgLinkView

The link text leading to the details page

CrudMsgTitleCreate Text

The title "Create [entity]"

CrudMsgTitleDelete Text

The title "Delete [entity]"

CrudMsgTitleUpdate Text

The title "Update [entity]"

CrudMsgTitleView Text

The title "Show [entity]"

CrudMsgViewLinkNext

The link text to return from object details page

defaultCrudMessage :: CrudMessage -> Text Source

Basic conversion of CRUD messages to English text.

defaultCrudAlertMessage Source

Arguments

:: Crud sub 
=> Route (CrudSubsite sub)

Route indicating the operation

-> Either SomeException (Obj sub)

Result of the operation

-> CrudM sub Html

Returns rendered message as HTML

Choose and render an appropriate alert message after a CRUD operation.

getMessenger :: CrudM sub (CrudMessage -> Text) Source

Retrieve the message translator and renderer in the CRUD monad. Uses getMessageRender behind the scenes, which calls your RenderMessage instance with the appropriate language headers.

Subsite routes

data family Route a

The type-safe URLs associated with a site argument.

Instances

RedirectUrl master (Route master) 
((~) * key Text, (~) * val Text) => RedirectUrl master (Route master, [(key, val)]) 
((~) * key Text, (~) * val Text) => RedirectUrl master (Route master, Map key val) 
Eq (Route LiteApp) 
Eq (Route WaiSubsite) 
Eq (ObjId sub) => Eq (Route (CrudSubsite sub)) 
Ord (Route LiteApp) 
Ord (Route WaiSubsite) 
Read (Route LiteApp) 
Read (Route WaiSubsite) 
Read (ObjId sub) => Read (Route (CrudSubsite sub)) 
Show (Route LiteApp) 
Show (Route WaiSubsite) 
Show (ObjId sub) => Show (Route (CrudSubsite sub)) 
data Route LiteApp = LiteAppRoute [Text] 
data Route WaiSubsite = WaiSubsiteRoute [Text] [(Text, Text)] 
data Route (CrudSubsite sub)  

getRouter :: CrudM sub (Route (CrudSubsite sub) -> Route (Site sub)) Source

Retrieve a child-to-parent route translator in the CRUD monad. Uses getRouteToParent behind the scenes, but it adapts based on whether we're being run in the site handler or a subsite handler.