mustache-0.3.1.0: A mustache template parser library.

Copyright(c) Justus Adam, 2015
LicenseLGPL-3
Maintainerdev@justus.science
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Text.Mustache.Types

Contents

Description

 

Synopsis

Types for the Parser / Template

type AST = [Node Text] Source

Abstract syntax tree for a mustache template

data Template Source

A compiled Template with metadata.

Constructors

Template 

Instances

data DataIdentifier Source

Kinds of identifiers for Variables and sections

Constructors

NamedData [Key] 
Implicit 

Types for the Substitution / Data

type Key = Text Source

Type of key used for retrieving data from Values

Converting

object :: [Pair] -> Value Source

Convenience function for creating Object values.

This function is supposed to be used in conjuction with the ~> and ~= operators.

Examples

  data Address = Address { ... }

  instance Address ToJSON where
    ...

  data Person = Person { name :: String, address :: Address }

  instance ToMustache Person where
    toMustache (Person { name, address }) = object
      [ "name" ~> name
      , "address" ~= address
      ]

Here we can see that we can use the ~> operator for values that have themselves a ToMustache instance, or alternatively if they lack such an instance but provide an instance for the ToJSON typeclass we can use the ~= operator.

(~>) :: ToMustache ω => Text -> ω -> Pair infixr 8 Source

Map keys to values that provide a ToMustache instance

Recommended in conjunction with the OverloadedStrings extension.

(↝) :: ToMustache ω => Text -> ω -> Pair infixr 8 Source

Unicode version of ~>

(~=) :: ToJSON ι => Text -> ι -> Pair infixr 8 Source

Map keys to values that provide a ToJSON instance

Recommended in conjunction with the OverloadedStrings extension.

(⥱) :: ToJSON ι => Text -> ι -> Pair infixr 8 Source

Unicode version of ~=

(~~>) :: (Conversion ζ Text, ToMustache ω) => ζ -> ω -> Pair infixr 8 Source

Conceptually similar to ~> but uses arbitrary String-likes as keys.

(~↝) :: (Conversion ζ Text, ToMustache ω) => ζ -> ω -> Pair infixr 8 Source

Unicde version of ~~>

(~~=) :: (Conversion ζ Text, ToJSON ι) => ζ -> ι -> Pair infixr 8 Source

Conceptually similar to ~= but uses arbitrary String-likes as keys.

(~⥱) :: (Conversion ζ Text, ToJSON ι) => ζ -> ι -> Pair infixr 8 Source

Unicode version of ~~=

class ToMustache ω where Source

Conversion class

Note that some instances of this class overlap delierately to provide maximum flexibility instances while preserving maximum efficiency.

Methods

toMustache :: ω -> Value Source

Instances

ToMustache Bool Source 
ToMustache Char Source 
ToMustache () Source 
ToMustache Scientific Source 
ToMustache Text Source 
ToMustache Value Source 
ToMustache Text Source 
ToMustache Value Source 
ToMustache [Char] Source 
ToMustache ω => ToMustache [ω] Source 
ToMustache ω => ToMustache (HashSet ω) Source 
ToMustache ω => ToMustache (Vector ω) Source 
ToMustache (Vector Value) Source 
Conversion θ Text => ToMustache (Context Value -> AST -> θ) Source 
ToMustache (Context Value -> AST -> Text) Source 
ToMustache (Context Value -> AST -> AST) Source 
ToMustache (AST -> Text) Source 
ToMustache (AST -> AST) Source 
(ToMustache α, ToMustache β) => ToMustache (α, β) Source 
(Conversion θ Text, ToMustache ω) => ToMustache (HashMap θ ω) Source 
ToMustache ω => ToMustache (HashMap Text ω) Source 
ToMustache (HashMap Text Value) Source 
(Conversion θ Text, ToMustache ω) => ToMustache (Map θ ω) Source 
(ToMustache α, ToMustache β, ToMustache γ) => ToMustache (α, β, γ) Source 
(ToMustache α, ToMustache β, ToMustache γ, ToMustache δ) => ToMustache (α, β, γ, δ) Source 
(ToMustache α, ToMustache β, ToMustache γ, ToMustache δ, ToMustache ε) => ToMustache (α, β, γ, δ, ε) Source 
(ToMustache α, ToMustache β, ToMustache γ, ToMustache δ, ToMustache ε, ToMustache ζ) => ToMustache (α, β, γ, δ, ε, ζ) Source 
(ToMustache α, ToMustache β, ToMustache γ, ToMustache δ, ToMustache ε, ToMustache ζ, ToMustache η) => ToMustache (α, β, γ, δ, ε, ζ, η) Source 
(ToMustache α, ToMustache β, ToMustache γ, ToMustache δ, ToMustache ε, ToMustache ζ, ToMustache η, ToMustache θ) => ToMustache (α, β, γ, δ, ε, ζ, η, θ) Source 

toTextBlock :: Conversion ζ Text => ζ -> Value Source

Converts arbitrary String-likes to Values

mFromJSON :: ToJSON ι => ι -> Value Source

Converts a value that can be represented as JSON to a Value.

Representation

type Array = Vector Value Source

A list-like structure used in Value

type Object = HashMap Text Value Source

A map-like structure used in Value

type Pair = (Text, Value) Source

Source type for constructing Objects

data Context α Source

Representation of stateful context for the substitution process

Constructors

Context [α] α 

type TemplateCache = HashMap String Template Source

A collection of templates with quick access via their hashed names