template-0.2.0.10: Simple string substitution

Safe HaskellSafe-Inferred
LanguageHaskell98

Data.Text.Template

Contents

Description

A simple string substitution library that supports "$"-based substitution. Substitution uses the following rules:

  • "$$" is an escape; it is replaced with a single "$".

    • "$identifier" names a substitution placeholder matching a mapping key of "identifier". "identifier" must spell a Haskell identifier. The first non-identifier character after the "$" character terminates this placeholder specification.
    • "${identifier}" is equivalent to "$identifier". It is required when valid identifier characters follow the placeholder but are not part of the placeholder, such as "${noun}ification".

Any other appearance of "$" in the string will result in an error being raised.

If you render the same template multiple times it's faster to first convert it to a more efficient representation using template and then render it using render. In fact, all that substitute does is to combine these two steps.

Synopsis

The Template type

data Template Source

A representation of a Text template, supporting efficient rendering.

Instances

The Context type

type Context = Text -> Text Source

A mapping from placeholders in the template to values.

type ContextA f = Text -> f Text Source

Like Context, but with an applicative lookup function.

Basic interface

template :: Text -> Template Source

Create a template from a template string. A malformed template string will raise an error.

templateSafe :: Text -> Either (Int, Int) Template Source

Create a template from a template string. A malformed template string will cause templateSafe to return Left (row, col), where row starts at 1 and col at 0.

render :: Template -> Context -> Text Source

Perform the template substitution, returning a new Text.

substitute :: Text -> Context -> Text Source

Perform the template substitution, returning a new Text. A malformed template string will raise an error. Note that

substitute tmpl ctx == render (template tmpl) ctx

showTemplate :: Template -> Text Source

Show the template string.

Applicative interface

renderA :: Applicative f => Template -> ContextA f -> f Text Source

Like render, but allows the lookup to have side effects. The lookups are performed in order that they are needed to generate the resulting text.

You can use this e.g. to report errors when a lookup cannot be made successfully. For example, given a list ctx of key-value pairs and a Template tmpl:

renderA tmpl (flip lookup ctx)

will return Nothing if any of the placeholders in the template don't appear in ctx and Just text otherwise.

substituteA :: Applicative f => Text -> ContextA f -> f Text Source

Perform the template substitution in the given Applicative, returning a new Text. Note that

substituteA tmpl ctx == renderA (template tmpl) ctx

Example

Here is an example of a simple substitution:

module Main where

import qualified Data.ByteString.Lazy as S
import qualified Data.Text as T
import qualified Data.Text.Lazy.Encoding as E

import Data.Text.Template

-- | Create 'Context' from association list.
context :: [(T.Text, T.Text)] -> Context
context assocs x = maybe err id . lookup x $ assocs
  where err = error $ "Could not find key: " ++ T.unpack x

main :: IO ()
main = S.putStr $ E.encodeUtf8 $ substitute helloTemplate helloContext
  where
    helloTemplate = T.pack "Hello, $name!\n"
    helloContext  = context [(T.pack "name", T.pack "Joe")]

The example can be simplified slightly by using the OverloadedStrings language extension:

{-# LANGUAGE OverloadedStrings #-}

module Main where

import qualified Data.ByteString.Lazy as S
import qualified Data.Text as T
import qualified Data.Text.Lazy.Encoding as E

import Data.Text.Template

-- | Create 'Context' from association list.
context :: [(T.Text, T.Text)] -> Context
context assocs x = maybe err id . lookup x $ assocs
  where err = error $ "Could not find key: " ++ T.unpack x

main :: IO ()
main = S.putStr $ E.encodeUtf8 $ substitute helloTemplate helloContext
  where
    helloTemplate = "Hello, $name!\n"
    helloContext  = context [("name", "Joe")]