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.GenId

Contents

Description

This module offers a monad transformer and a class for page-unique identifier generation. To use it, simply add a state monad to your monad stack with a state type that is an instance of the HasIdStream class (you can simply use Stream Identifier, if you don't need any other state). See the newId action to see the exact type of stack you need.

To construct the initial state you can use the predefined idsFrom function. It constructs a stream of unique identifiers from its argument character set.

To generate a new identifier use the newId action within your monad stack. The generated identifiers are of type Identifier. There are helper functions for integrating an identifer into markup and the stylesheet. See the DOM helpers and the CSS helpers sections in this module. Also see the documentation for Identifier for more detailed information and an example.

Hint: It is perfectly valid to combine a widget writer and an identifier generator, so you don't need to alternate between constructing widgets and generating identifiers.

Synopsis

Unique identifiers

newtype Identifier Source

Identifiers that can be used with clay, jmacro and blaze-html.

An identifier of this type is supposed to be used for DOM ids, classes or similar names. Note that the ToJExpr instance converts it to a JavaScript string, so that you can use it with jQuery or functions like getElementById. When using jQuery, remember that it expects selector syntax as in the following example:

myWidget ::
    ( HasIdStream s,
      MonadState s m,
      MonadWidget url (MySection -> Html) m )
    => m ()
myWidget = do
    myId <- newId
    addSection MySection (H.p "My boring paragraph." ! domId myId)
    addStyle $ idSel myId ? background gray
    addStyle $ idSel myId # ".groovy" ? do
        background darkblue
        color pink
        fontWeight bold
    addScriptLink "static/jquery.js"
    addScript [jmacro|
        fun init ->
            window.setTimeout
                (\() {
                    $("#" + `myId`).addClass("groovy");
                    $(".groovy").text("My groooovy paragraph!") })
                2500;
        $(init) |]

Constructors

Identifier 

Fields

identifier :: String
 

class HasIdStream a where Source

Instances of this class are types that embed an identifier stream.

Methods

idStream :: Lens' a (Stream Identifier) Source

Lens into the identifier stream.

idsFrom :: [Char] -> Stream Identifier Source

Infinite stream of identifiers built from the given character set. The stream is sorted by identifier length, shortest first.

newId :: (HasIdStream a, MonadState a m) => m Identifier Source

Fetches the next identifier.

DOM helpers

classId :: Identifier -> Attribute Source

HTML5 class attribute containing the given identifier.

customId :: Tag -> Identifier -> Attribute Source

Custom attribute containing the given identifier.

dataId :: Tag -> Identifier -> Attribute Source

HTML5 data attribute (data-*) containing the given identifier.

domId :: Identifier -> Attribute Source

HTML5 id attribute containing the given identifier.

CSS helpers

idRef :: Identifier -> Refinement Source

Id refinement for the given identifier.

idSel :: Identifier -> Selector Source

Id selector for the given identifier.

classRef :: Identifier -> Refinement Source

Class refinement for the given identifier.

classSel :: Identifier -> Selector Source

Class selector for the given identifier.