lambdacms-core-0.3.0.2: LambdaCms 'core' subsite for Yesod apps

Safe HaskellNone
LanguageHaskell2010

LambdaCms.Core.Foundation

Synopsis

Documentation

data Allow a Source

Specifies the criteria for authorizing a request.

Constructors

AllowAll

Allow any request (no authentication required).

AllowAuthenticated

Allow requests in authenticated sessions.

AllowRoles a

Allow requests in authenticated sessions belonging to users that have at least one matching role. See the isAuthorizedTo function for details.

AllowNone

Allow no requests at all.

data AdminMenuItem master Source

A menu item, also see adminMenu.

MenuItem (SomeMessage MsgProduct) (ProductAdminOverviewR) "shopping-cart"

Constructors

MenuItem 

Fields

label :: SomeMessage master

The text of the item (what the user sees).

route :: Route master

The Route to which it points.

icon :: Text

A glyphicon without the ".glyphicon-" prefix.

type CoreHandler a = forall master. LambdaCmsAdmin master => HandlerT CoreAdmin (HandlerT master IO) a Source

Alias for the fairly complex HandlerT type that allows persistent queries on the master's db connection.

type CoreForm a = forall master. LambdaCmsAdmin master => Html -> MForm (HandlerT master IO) (FormResult a, WidgetT master IO ()) Source

Alias for the fairly complex Form type.

class (YesodAuth master, AuthId master ~ Key User, AuthEntity master ~ User, YesodAuthPersist master, YesodPersistBackend master ~ SqlBackend, ParseRoute master, Ord (Roles master), Enum (Roles master), Bounded (Roles master), Show (Roles master), Eq (Roles master)) => LambdaCmsAdmin master where Source

Associated Types

type Roles master Source

A type denoting the roles a user can have on the website. The implementation must have a datatype representing those roles. For example:

type Roles MyApp = MyRoles

Then, in the base app, MyRoles can be:

data MyRoles = Admin
             | SuperUser
             | Blogger
             deriving (Show, Eq, Read, Ord, Enum, Bounded)

Methods

getUserRoles :: Key User -> HandlerT master IO (Set (Roles master)) Source

Get all roles of a user as a Set.

setUserRoles :: Key User -> Set (Roles master) -> HandlerT master IO () Source

Replace the current roles of a user by the given Set.

mayAssignRoles :: HandlerT master IO Bool Source

defaultRoles :: HandlerT master IO (Set (Roles master)) Source

Gives the default roles a user should have on create

isAuthorizedTo Source

Arguments

:: master 
-> Maybe (Set (Roles master))

Set of roles the user has.

-> Allow (Set (Roles master))

Set of roles allowed to perform the action.

-> AuthResult 

Authorize a request to perform an action. If a user session is present it can use the specified Roles to do so.

actionAllowedFor Source

Arguments

:: Route master

The action (or route).

-> ByteString

The request method (e/g: GET, POST, DELETE, ...). Knowing which method is used allows for more fine grained permissions than only knowing whether it is write request.

-> Allow (Set (Roles master)) 

Get the Allow type needed for this action. The default is that no one can do anything.

coreR :: Route CoreAdmin -> Route master Source

Both coreR and authR are used to navigate to a different controller. It saves you from putting "getRouteToParent" everywhere.

authR :: Route Auth -> Route master Source

masterHomeR :: Route master Source

Gives the route which LambdaCms should use as the master site homepage.

adminTitle :: SomeMessage master Source

welcomeWidget :: Maybe (WidgetT master IO ()) Source

Gives a widget to use as the welcome banner on the admin dashboard

adminLayout :: WidgetT master IO () -> HandlerT master IO Html Source

Applies some form of layout to the contents of an admin section page.

adminAuthLayout :: WidgetT master IO () -> HandlerT master IO Html Source

authLogoR :: Route master Source

adminMenu :: [AdminMenuItem master] Source

A list of menu items to show in the backend. Each site is different so what goes in the list should be provided by the Base app.

[ MenuItem (SomeMessage MsgUser)    (UserAdminOverciewR)    "user"
, MenuItem (SomeMessage MsgProduct) (ProductAdminOverviewR) "shopping-cart" ]

renderCoreMessage :: master -> [Text] -> CoreMessage -> Text Source

Renders a Core Message.

renderLanguages :: master -> [Text] Source

A list of languages to render.

lambdaCmsSendMail :: Mail -> HandlerT master IO () Source

A default way of (not) sending email: just print it to the stdout. See https://github.com/lambdacms/lambdacms/blob/master/docs/implement-mail-deivery-method.md for instructions on implementing a real delivery method.

authenticateByLambdaCms :: LambdaCmsAdmin master => Creds master -> HandlerT master IO (AuthenticationResult master) Source

Ensures the admin user's lastLogin property is updated with logging in.

lambdaCmsMaybeAuthId :: LambdaCmsAdmin master => HandlerT master IO (Maybe (AuthId master)) Source

Replace defaultMaybeAuthId with this function to ensure (for every request to the admin interface) that admin users are required to have an active account. TODO: Provide a bit more feedback then the standard 404 page when denying access.

canFor Source

Arguments

:: LambdaCmsAdmin master 
=> master 
-> Maybe (Set (Roles master))

Set of Roles the user has.

-> Route master

The action to perform.

-> ByteString

The requested method (e/g: GET, POST, ...).

-> Maybe (Route master)

ust route when the user is allowed to perform the action, Nothing otherwise.

Checks whether a user is allowed perform an action and returns the route to that action if he is. This way, users only see routes they're allowed to visit.

getCan :: LambdaCmsAdmin master => HandlerT master IO (Route master -> ByteString -> Maybe (Route master)) Source

A wrapper function that gets the roles of a user and calls canFor with it. This is what you'll use in a handler.

can <- getCan

Then, in hamlet:

$maybe r <- can (SomeRouteR)
  ... @{r}

defaultCoreAdminMenu :: LambdaCmsAdmin master => (Route CoreAdmin -> Route master) -> [AdminMenuItem master] Source

A default admin menu.

adminLayoutSub :: LambdaCmsAdmin master => WidgetT sub IO () -> HandlerT sub (HandlerT master IO) Html Source

Shorcut for rendering a subsite Widget in the admin layout.

withName :: Text -> FieldSettings site -> FieldSettings site Source

Extension for bootstrap (give a name to input field).

lambdaCmsHumanTimeLocale :: LambdaCmsAdmin master => HandlerT master IO HumanTimeLocale Source

Wrapper for humanReadableTimeI18N'. It uses Yesod's own i18n functionality.

routeBestMatch :: RenderRoute master => Maybe (Route master) -> [Route master] -> Maybe (Route master) Source

class LambdaCmsLoggable master entity where Source

Methods

logMessage :: master -> ByteString -> entity -> [(Text, Text)] Source

Instances

LambdaCmsAdmin master => LambdaCmsLoggable master User Source 

translateUserLogs :: forall b master. (LambdaCmsAdmin master, RenderMessage master b) => master -> (Text -> b) -> User -> [(Text, Text)] Source

logUser :: LambdaCmsAdmin master => User -> HandlerT master IO [(Text, Text)] Source

logAction :: LambdaCmsAdmin master => [(Text, Text)] -> HandlerT master IO () Source