servant-ede-0.4: Combinators for rendering EDE templates in servant web applications

Copyright(c) 2015 Alp Mestanogullari
LicenseBSD3
MaintainerAlp Mestanogullari <alpmestan@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Servant.HTML.EDE

Contents

Description

Combinators for rendering ede templates in servant web applications.

Synopsis

Introduction

The ede library provides a reasonably good template engine. This package explores a smooth integration of ede into servant through two combinators.

Explicitly binding data to a template

The first combinator is Tpl, which is used for generating web pages from ede templates by explicitly returning an Object (which is a synonym for HashMap Text Value, i.e a JSON object) from the handler which will then be rendered against a given template.

-- we want our template file, index.html,
-- to be rendered under /index
type API = "index" :> Tpl "index.html"

api :: Proxy API
api = Proxy

server :: Server API
server = return indexData

  where indexData :: Object
        indexData =
          HM.fromList [ ("company_name", "Foo Inc.")
                      , ("ceo", "Bar Baz")
                      ]

main :: IO ()
main = do
  -- this tells the library to look for index.html
  -- under the ./templates directory
  loadTemplates api "./templates"
  run 8080 server

Note that if your template doesn't need any data, you can just return the empty Object, with Data.Monoid's mempty.

The call to loadTemplates is mandatory. It loads and compiles all the templates used in your API and puts them in a global "compiled template store". I'm not really satisfied with this, see the Global template store section for more on this topic.

Template rendering as a content-type

The other way to use this package is reminiscent of how you can render HTML with servant-blaze or its cousin servant-lucid. Indeed, this package provides an HTML content type just like the two aforementionned libraries. However, unlike in these packages, this HTML type is parametrised by a type-level string meant to be the name of the template file (or path to the template file starting from a "root" directory of templates).

In the same way that servant's standard JSON combinator carries the precise way in which we encode haskell values to JSON, in addition to representing the application/json content type, HTML carries the template used to render values of a given type.

If we wanted to have a /user endpoint accessible in JSON or HTML, returning a user, we could write:

type UserAPI = "user" :> Get '[JSON, HTML "user.tpl"] User

userAPI :: Proxy UserAPI
userAPI = Proxy

How, then, can servant know how to marshall User to the template in order to render it? Simple, you just have to provide an instance of the following ToObject class:

class ToObject a where
  toObject :: a -> Object

If our User data type is:

data User = User { name :: String, age :: Int }

we can simply do, using functions from Text.EDE:

instance ToObject User where
  toObject u =
    fromPairs [ "name" .= name u
              , "age"  .= age u
              ]

However, this is actually not necessary. This library provides can derive the ToObject instance for you as long as your data type derives the GHC.Generics.Generic class, which can be done by specifying {--} at the top of your module, adding import GHC.Generics and by changing the User data type declaration to:

data User = User { name :: String, age :: Int } deriving Generic

You can then simply write:

instance ToObject User

and the library will figure out how to encode User to JSON for you. IMPORTANT: This only works with data types with a single record and field selectors.

Now we can put this all to work with a simple webservice:

server :: Server UserAPI
server = return (User "lambdabot" 31)

main :: IO ()
main = do
  loadTemplates userAPI "./templates"
  run 8082 (serve userAPI server)

Again, the call to loadTemplates is mandatory because the HTML content type relies on having its hands on already-compiled templates.

You can now write a user.tpl template under the ./templates directory using any of ede's constructs, assuming that a name string variable and an age int variable are in scope.

Reference

Tpl combinator, for explicit data binding

data Tpl tplfile Source

Combinator for serving EDE templates without arguments. Usage:

type API = "index" :> Tpl "index.tpl"
      :<|> "about" :> Tpl "about.tpl"

api :: Proxy API
api = Proxy

server :: Templates -> Server API
server tpls = return mempty :<|> return mempty

main :: IO ()
main = do
  loadTemplates_ api "./templates"
  run 8080 (serve api server)

Instances

KnownSymbol tplfile => HasServer * (Tpl tplfile)

The so-called "request handler" for an endpoint ending with Tpl just has to be the opaque Templates value returned by loadTemplates applied to your API, which is just a compiled template store indexed by file name.

type TemplateFiles * (Tpl f) = (:) Symbol f ([] Symbol) 
type ServerT * (Tpl tplfile) m = m Object 

HTML content type, for serializing data types to HTML

data HTML tplfile Source

HTML content type, but more than just that.

HTML takes a type-level string which is a filename for the template you want to use to render values. Example:

type UserAPI = "user" :> Get '[JSON, HTML "user.tpl"] User

userAPI :: Proxy UserAPI
userAPI = Proxy

data User = User { name :: String, age :: Int } deriving Generic

instance ToJSON User
instance ToObject User

server :: Server API
server = return (User "lambdabot" 31)

main :: IO ()
main = do
  loadTemplates userAPI "./templates"
  run 8082 (serve userAPI server)

This will look for a template at ./templates/user.tpl, which could for example be:

<ul>
  <li><strong>Name:</strong> {{ name }}</li>
  <li><strong>Age:</strong> {{ age }}</li>
</ul>

Instances

Accept * (HTML tplfile)
text/html;charset=utf-8
(KnownSymbol tplfile, ToObject a) => MimeRender * (HTML tplfile) a 

class ToObject a where Source

Turn haskell values into JSON objects.

This is the mechanism used by EDE to marshall data from Haskell to the templates. The rendering is then just about feeding the resulting Object to a compiled Template. Example:

import Text.EDE

data User = User { name :: String, age :: Int }
instance ToObject User where
  toObject user =
    fromPairs [ "name" .= name user
              , "age"  .= age user
              ]

However, you're not forced to write the instance yourself for such a type. Indeed, for any record type (i.e a datatype with a single constructor and with field selectors) you can let GHC.Generics derive the ToObject instance for you.

data User = User { name :: String, age :: Int } deriving Generic
instance ToObject User

This will generate an equivalent instance to the previous one.

Minimal complete definition

Nothing

Methods

toObject :: a -> Object Source

Turn values of type a into JSON Objects.

-- Reminder:
type Object = HashMap Text Value

Instances

Loading templates

loadTemplates Source

Arguments

:: (Reify (TemplateFiles api), Applicative m, MonadIO m) 
=> Proxy api 
-> FilePath

root directory for the templates

-> m Errors 

Same as loadTemplates, except that it initializes a global template store (i.e a Templates value) and fills it with the resulting compiled templates if all of them are compiled successfully. If that's not the case, the global template store (under an MVar) is left empty.

IMPORTANT: Must always be called before starting your servant application.

type TemplateError = (FilePath, String) Source

A TemplateError is a pair of a template filename and the error string for that file.

Helpers

type family TemplateFiles api :: [Symbol] Source

Collect all the template filenames of an API as a type-level list of strings, by simply looking at all occurences of the Tpl and HTML combinators and keeping the filenames associated to them.

Instances

type TemplateFiles * (Tpl f) = (:) Symbol f ([] Symbol) 
type TemplateFiles * ((:<|>) a b) 
type TemplateFiles * (Get cs a) 
type TemplateFiles * (Post cs a) 
type TemplateFiles * (Delete cs a) 
type TemplateFiles * (Put cs a) 
type TemplateFiles * (Patch cs a) 
type TemplateFiles * ((:>) k k1 a r) = TemplateFiles k1 r 

class Reify symbols where Source

Helper class to reify a type-level list of strings into a value-level list of string. Used to turn the type-level list of template file names into a value-level list.

Methods

reify :: Proxy symbols -> [String] Source

Instances

Reify ([] Symbol) 
(KnownSymbol s, Reify symbols) => Reify ((:) Symbol s symbols) 

Global template store

Why have a global template store? Well, while for Tpl we can run arbitrary code in the handlers, take arguments and what not, that's not the case when writing the MimeRender instance for HTML.

All we have is a value of some type and we have to pull a compiled template out of thin air. That's why we use a global MVar-protected template store indexed by filename. It's filled once at the beginning when you call loadTemplates and is then only accessed in a read-only fashion. I would be interested in hearing about any suggestion, improvement or replacement for this. If you have an idea, feel free to shoot me an email at the address specified in the cabal description.