HStringTemplate

From HaskellWiki
Revision as of 16:23, 2 July 2009 by Sclv (talk | contribs)
Jump to navigation Jump to search


HStringTemplate is a Haskell-ish port of the Java StringTemplate library by Terrence Parr, ported by Sterling Clover. It can be used for any templating purpose, but is often used for dynamically generated web pages.

For news of HStringTemplate and blog items, see Sterling Clover's blog, and for downloads and API docs see hackage.

Additional helper functions for HStringTemplate can be found in the HStringTemplateHelpers package

This page is work in progress, and aims to supplement the API docs with tutorial style documentation and template syntax documentation.

Getting started

Assuming you have installed the library, try the following at a GHCi prompt:

Prelude> :m + Text.StringTemplate
Prelude Text.StringTemplate> let t = newSTMP "Hello $name$" :: StringTemplate String

This has created a 'String' based StringTemplate. StringTemplates can be based around any 'Stringable' type, allowing you to use ByteString's or any other type if you write the Stringable instance. The template has a single 'hole' in it called 'name', delimited by dollar signs.

We can now fill in the hole using 'setAttribute', and render it to its base type (String in this case):

Prelude Text.StringTemplate> render $ setAttribute "name" "Joe" t
"Hello Joe"

Instead of "Joe", we can use anything that has a ToSElem instance.

There are shortcuts for long attribute chains, such as setManyAttributes and renderf

(TODO - how does renderf work?)

The following example shows the use of renderf, which, like printf, is overloaded on multiple arguments. (This unfortunately means that type signatures may be necessary). This example also shows how repeatedly setting a single attribute in fact creates a list.

Prelude Text.StringTemplate> renderf (newSTMP "hello $names;separator='; '$" :: StringTemplate String) ("names","joe") ("names", "jeff") ("names","mort"):: String
"hello mort; jeff; joe"


Expression syntax

This section follows http://www.antlr.org/wiki/display/ST/Expressions for structure, adapting as appropriate. Syntax not mentioned below should be assumed to be implemented as per the Java version of StringTemplate. (Please add notes if you find anything missing or different).

Named attributes

The most common thing in a template besides plain text is a simple named attribute reference such as:

Your email: $email$

When the template is rendered, it will lookup "email" in its environment and convert it to the type of the underlying StringTemplate. (Usually this occurs via a conversion to String, but this can be avoided using setNativeAttribute e.g. if you have a StringTemplate ByteString you can use setNativeAttribute with ByteString objects to avoid the round trip to Strings. This also avoids the encoding function that has been set on the template.)

If "email" does not exist in the template environment, the above will render as if "email" was set to the empty string.

The Maybe data structure can be used as the value of an attribute, and will render as a null attribute (by default the empty string) if 'Nothing', otherwise it will render just like the data contained in the 'Just' structure.

If the attribute is a list, the elements are rendered one after the other. To use a separator in between items, use the separator option:

$values; separator=", "$

If this is rendered with "values" set to [1..4] the result will be:

1, 2, 3, 4

If the "values" is set to [Just 1, Nothing, Just 3] the result will be:

1, , 3

This follows from the treatment of Nothing described above. Use Maybe.catMaybes to remove the 'Nothing's if needed. Null values can also be removed within a template through use of the "strip" function. Or, to emit a special value for each Nothing element in the list, use the null option:

$values; null="missing"; separator=", "$

This would render the previous example as:

1, missing, 3

Note the difference between this and the Java StringTemplate -- the 'null' option and the 'separator' option have a semicolon (;) between them, and not a comma (,). (Is this a bug?)

Compound values

Tuples

The simplest type of compound value is a tuple. Tuples are rendered by indexing the elements from zero and using these indices as labels. For instance, this template:

$value; separator=", "$

with "value" set to (1, "test", Just 2.0) will render as:

0: [1], 1: [test], 2: [2.0]

Custom datastructures

Suppose you have a data definition for a Person which holds a name and age:

data Person = Person String Int

We can get this to render in the same way as a tuple by making 'Person' an instance of 'ToSElem'. The easiest way to do that is to use Text.StringTemplate.GenericStandard. Make the following changes:

{-# LANGUAGE DeriveDataTypeable #-}

import Data.Typeable
import Data.Data
import Text.StringTemplate
import Text.StringTemplate.GenericStandard

data Person = Person String Int
                deriving (Data, Typeable)

(See Stand-alone deriving declarations if you are not able to change the definition of your data structure)

However, it will be more useful to name the fields:

data Person = Person { name :: String
                     , age ::Int
                     } deriving (Data, Typeable)

With this change, using ", " as the separator, a value Person { name = "Joe", age = 23 } will render as:

age: [1], name: [Joe]

Accessing fields

Obviously you will usually want to access the fields individually. This can be done using a dot followed by an integer for tuples or the name of the field for records. For example, we could have a template like this:

Hello $names.0$,
Your full name is $person.name$ and you are $person.age$ years old.

With "person" set to Person { name = "Joe Bloggs", age = 23 } and "names" set to a tuple containing the same name parsed into a first-name, last-name pair ("Joe", "Bloggs"), this would render as:

Hello Joe,
Your full name is Joe Bloggs and you are 23 years old.

Data.Map

Instance of Data.Map can also be used as attributes, and the values can be retrieved using the key as the field name e.g. to produce the same result as the last example, "person" could be set to

Data.Map.fromList [("name", "Joe Bloggs"), ("age", "23")]

Using GenericWithClass

(TODO)

Template references

Template references, template application and anonymous templates work as in the Java version. Note that you will need to create template groups (STGroup) in order for one template to be able to reference another.


Encoder functions

(TODO. NB - can avoid use of encoder function by setting ByteString attributes (?))

Custom formatting

(TODO)

Template groups

(TODO. Including strategies for template re-use)

Loading templates from disk

You will probably want to load templates from the file system instead of embedding them into Haskell source files. To do this:

  • Create a directory to store the templates
  • Create a template in it with the extension ".st" e.g "mytemplate.st"
  • Load the template like the following example code:
import Data.ByteString.Lazy (ByteString)
import Text.StringTemplate
import Maybe (fromJust)
 
main = do
  templates <- directoryGroup "/path/to/your/templates/" :: IO (STGroup ByteString)
  let t = fromJust $ getStringTemplate "mytemplate" templates
  print $ render t

If you have IO errors or the template does not exist, you will get an exception — error handling code is left as an excercise for the reader...

The type of directoryGroup result has to be specified, otherwise it does not know what type of StringTemplate to return. We have specified ByteString because the file system really stores byte streams, and we want to load the file uninterpreted (Haskell libraries do not just "do the right thing" with encodings, since in general that is not possible).