| Copyright | (c) Alp Mestanogullari 2015 |
|---|---|
| Maintainer | alpmestan@gmail.com |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
Servant.EDE
Description
Rendering EDE templates with servant.
This package provides two combinators to be used as content-types
with servant (i.e just like JSON), HTML and Tpl.
HTMLtakes a filename as parameter and lets you render the template with that name against the data returned by a request handler using thetext/html;charset=utf-8MIME type, XSS-sanitizing the said data along the way. SeeHTMLfor an example.Tpldoes the same except that it's parametrized over the content type to be sent along with the rendered template. Any type that has anAcceptinstance will do. SeeTplfor an example.
- data HTML file
- data Tpl ct file
- class ToObject a where
- loadTemplates :: (Reify (TemplateFiles api), Applicative m, MonadIO m) => Proxy api -> FilePath -> m Errors
- type family TemplateFiles api :: [Symbol]
- class Reify symbols
- data Templates
- type Errors = [TemplateError]
- type TemplateError = (FilePath, String)
Combinators
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. Just like Tpl, types used with
the HTML content type (like User below)
must provide a ToObject instance.
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 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>IMPORTANT: it XSS-sanitizes every bit of text in the Object
passed to the template.
Instances
| Accept * (HTML file) | text/html;charset=utf-8 |
| (KnownSymbol file, ToObject a) => MimeRender * (HTML file) a | XSS-sanitizes data before rendering it |
A generic template combinator, parametrized over the content-type (or MIME) associated to the template.
The first parameter is the content-type you want to send along with
rendered templates (must be an instance of Accept).
The second parameter is the name of (or path to) the template file.
It must live under the FilePath argument of loadTemplates.
Any type used with this content-type (like CSSData below)
must have an instance of the ToObject class. The field names
become the variable names in the template world.
Here is how you could render and serve, say, CSS
(Cascading Style Sheets) templates that make use
of some CSSData data type to tweak the styling.
data CSS
instance Accept CSS where
contentType _ = "text" // "css"
type StyleAPI = "style.css" :> Get '[Tpl CSS "style.tpl"] CSSData
styleAPI :: Proxy StyleAPI
styleAPI = Proxy
data CSSData = CSSData
{ darken :: Bool
, pageWidth :: Int
} deriving Generic
instance ToObject CSSData
server :: Server API
server = -- produce a CSSData value depending on whatever is relevant...
main :: IO ()
main = do
loadTemplates styleAPI "./templates"
run 8082 (serve styleAPI server)
This will look for a template at ./templates/style.tpl,
which could for example be:
body {
{% if darken %}
background-color: #222222;
color: blue;
{% else %}
background-color: white;
color: back;
{% endif %}
}
#content {
width: {{ pageWidth }};
margin: 0 auto;
}A complete, runnable version of this can be found
in the examples folder of the git repository.
Instances
| Accept * ct => Accept * (Tpl ct file) | |
| (KnownSymbol file, Accept * ct, ToObject a) => MimeRender * (Tpl ct file) a |
Sending Haskell data to templates
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 UserThis will generate an equivalent instance to the previous one.
Minimal complete definition
Nothing
Methods
Loading template files (mandatory)
Arguments
| :: (Reify (TemplateFiles api), Applicative m, MonadIO m) | |
| => Proxy api | |
| -> FilePath | root directory for the templates |
| -> m Errors |
This function 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. Example:
type API = Get '[HTML "home.tpl"] HomeData api :: Proxy API api = Proxy main :: IO () main = loadTemplates api "path/to/templates" >>= print
This would try to load home.tpl, printing any error or
registering the compiled template in a global (but safe)
compiled template store, if successfully compiled.
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 * Raw = [] 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 |
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.
Minimal complete definition
An opaque "compiled-template store".
The only way to get a value of this type is to use
loadTemplates on a proxy of your API.
This ensures that when we lookup a template (in order
to render it) in our Templates store, we are
guaranteed to find it.
type Errors = [TemplateError] Source
A list of TemplateErrors.
type TemplateError = (FilePath, String) Source
A TemplateError is a pair of a template filename
and the error string for that file.