Web-page ======== This package combines blaze-html, clay and jmacro into a framework-agnostic library to generate web pages dynamically from individual components. It is inspired by Yesod's widgets, but is more general, more powerful and can be used with other web frameworks. Features -------- The `Widget` type is very expressive. The following features are built in: * works with your web framework of choice, * fully embedded stylesheet and script languages (jmacro and clay), * page-specific or external stylesheets and script, * type-safe routing, * flexible polymorphic body type, * monoidal piece-by-piece construction of pages, * hierarchial titles, * additional head markup, * optional lens interface, * rendering to multiple documents (e.g. separate stylesheet and script). Other features are add-ons: * non-HTML bodies (e.g. Pandoc integration), * multipart bodies aka *sections*, * page-unique identifier generation. Usage ----- This is a brief overview of the process to construct and render a web page using this library. First of all you will need a few extensions: {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} The `OverloadedStrings` extension is optional, but makes writing blaze-html markup and clay stylesheets a lot more convenient. The `QuasiQuotes` extension is only required for jmacro, if you need scripts in your widgets. With that aside the first step is to understand the `Widget` type: Widget url h The type argument `url` is your URL type. If you don't use type-safe routing, then simply use `url = Text`. This is only significant for external stylesheets and scripts. If you don't use any of them, just leave it polymorphic. The second type argument `h` is the page body type. For now just use `Html` (from blaze-html), which means that the body of your page will be simple unstructured HTML markup. ### Construction `Widget` is a family of monoids. While you could use the `Monoid` interface directly it's usually much more convenient to use a writer monad to construct your widgets. In most cases the correct type will be inferred, but we will specify it regardless: myWidget :: (MonadWriter (Widget url Html) m) => m () If you are like me, you prefer to write type signatures for your top-level definitions. A constraint alias is provided for your convenience. The following type signature is equivalent to the above: myWidget :: (MonadWidget url Html m) => m () If writer is the only effect you need, there is an even simpler alias that you can use, which is equivalent to the above as well: myWidget :: WidgetWriter url Html () Now we can construct the widget piece by piece: myWidget = do setTitle "Hello" addBody (H.h1 "Hello") addBody (H.p "Hello world!") addStyle $ html ? do background white color black You can build the widget by reducing the writer: w :: Widget url Html w = execWriter myWidget This widget can now be rendered to a page. ### Rendering To render the widget you can use the `renderWidget` function: renderWidget :: ([Text] -> Tl.Text) -> Widget Text Html -> Page The `Text` type is the strict version, while the `Tl.Text` type is the lazy version. The first argument to this function is the title renderer. Widgets define an optional title, which is not just a text string, but a list of text strings. That's because this library supports hierarchial titles by using the `withTitle` function. We will not cover this here. Just use `titleMinor`: page :: Page page = renderWidget (titleMinor " - ") w Pages are an intermediate step between rendering and delivery. They are necessary, because this library allows you to render to multiple documents, for example to a markup document, a stylesheet and a script. You can then use a clever hash-based routing mechanism to tell clients to cache stylesheets and scripts forever and reduce the required bandwidth to a minimum. ### Realisation To process of finalising a page to an actual set of documents that you can deliver is referred to as *realisation*. We will simply render to a single document with an inline stylesheet and no script (because our widget above doesn't define one). The `realiseInline` function does exactly that: realiseInline :: Page -> Builder All we need to do is to apply it to our page: document :: Builder document = realiseInline page The `Builder` type is the usual one from blaze-builder. Most web frameworks use it for efficient bytestring concatenation and provide a simple interface to deliver those strings to clients. For example WAI provides the `responseBuilder` function. If you want to save the result to a file, just use `toLazyByteString` or `toByteStringIO`.