web-page-0.2.0: Monoidally construct web pages

Copyright(c) 2014 Ertugrul Soeylemez
LicenseBSD3
MaintainerErtugrul Soeylemez <ertesx@gmx.de>
Safe HaskellNone
LanguageHaskell2010

Web.Page.Widget

Contents

Description

A widget is a self-contained web page component represented by the Widget type. This type is a family of monoids, so you can use it together with a writer monad, which is the preferred way to construct widgets.

Synopsis

Page widgets

data Widget url h Source

A widget is a self-contained fragment of a web page together with its scripts and styles. This type is inspired by Yesod's widgets, but is supposed to be constructed by using a writer monad and does not denote effects of its own.

To construct widgets through a writer monad, you can use the add* functions like addSection or addStyle:

do addSection "header" (H.h1 "My fancy header")
   addStyle $ html ? do
       background yellow
       color black

Alternatively use can use lens combinators like scribe and censoring together with widget lenses like wSection and wStyle:

do scribe (wSection "header") (H.h1 "My fancy header")
   scribe wStyle $ html ? do
       background yellow
       color black

The title is constructed by using withTitle and setTitle. This allows you to have a hierarchy of titles with a site title, a page title and even a component title:

withTitle "My site title" $
    withTitle "My department title" $
        setTitle "My page title"
        addSection "header" (H.h1 "My page title")

The first type argument url is the type of URLs. You may use it for type-safe routing. If you don't use type-safe routing, you can simply use Text.

The second type argument h is the body type. For simple pages you can use Html, but this widget type allows you to have more complicated bodies, as long as you reduce them to Html at some point. For example this library predefines functions like addSection and flattenBody to allow you to construct individual page sections separately and then merge them. You can use it for example to divide your document into a header, a menu, a content area and a footer, and every widget can contribute to each of those sections separately.

Another way to use this is to construct your body using a completely different document type, for example a Pandoc document, then later convert it to Html.

Constructors

Widget 

Fields

_wBody :: h

Markup body.

_wHead :: Html

Head content.

_wScript :: JStat

Inline scripts.

_wScriptLinks :: Set url

External scripts.

_wStyle :: Css

Stylesheet.

_wStyleLinks :: Set url

External stylesheets.

_wTitle :: Last [Text]

Page title chunks (outermost first).

Instances

Functor (Widget url) 
Ord url => Applicative (Widget url) 
Foldable (Widget url) 
(Monoid h, Ord url) => Monoid (Widget url h) 
Typeable (* -> * -> *) Widget 

Widget actions

type MonadWidget url h = MonadWriter (Widget url h) Source

Convenient constraint alias for widget actions.

type WidgetWriter url h a = forall m. MonadWidget url h m => m a Source

Convenient type alias for polymorphic widget actions.

Constructing widgets

addBody :: h -> WidgetWriter url h () Source

Construct a widget with the given body. Use this combinator if you don't need sections.

addHead :: Html -> WidgetWriter url h () Source

Construct a widget with the given head markup.

addScript :: JStat -> WidgetWriter url h () Source

Construct a widget with the given script.

addScriptLink :: url -> WidgetWriter url h () Source

Construct a widget with the given script link.

addSection :: Eq k => k -> h -> WidgetWriter url (k -> h) () Source

Construct a widget with the given body section.

addStyle :: Css -> WidgetWriter url h () Source

Construct a widget with the given stylesheet.

addStyleLink :: url -> WidgetWriter url h () Source

Construct a widget with the given style link.

setTitle :: Text -> WidgetWriter url h () Source

Scribe the title of the widget. Use this function to construct the lowest level title. For higher level titles use withTitle. The most recently set title wins.

withTitle :: MonadWidget url h m => Text -> m a -> m a Source

Prepend the given title chunk to the given widget action. Conceptually this wraps the given widget in a higher level title. Use setTitle for the lowest level title.

Widget lenses

wBody :: Lens' (Widget url h) h Source

Lens into a widget's body.

wHead :: Lens' (Widget url h) Html Source

Lens into a widget's head.

wScript :: Lens' (Widget url h) JStat Source

Lens into a widget's inline script.

wScriptLinks :: Lens' (Widget url h) (Set url) Source

Lens into a widget's external scripts.

wSection :: Eq k => k -> Lens' (Widget url (k -> h)) h Source

Lens into a specific section of a widget.

wStyle :: Lens' (Widget url h) Css Source

Lens into a widget's inline style.

wStyleLinks :: Lens' (Widget url h) (Set url) Source

Lens into a widget's external styles.

wTitle :: Lens' (Widget url h) (Last [Text]) Source

Lens into a widget's title.

Mapping

flattenBody :: Monoid h => [k] -> Widget url (k -> h) -> Widget url h Source

Flatten the given widget's body by joining the given sections into a single section. It's valid to list sections more than once.

mapLinksA :: (Applicative f, Ord url) => (url' -> f url) -> Widget url' h -> f (Widget url h) Source

Map the given action over all URLs in the given widget.

mapLinksM :: (Monad m, Ord url) => (url' -> m url) -> Widget url' h -> m (Widget url h) Source

Monadic version of mapLinksA.