Skip to content

Instantly share code, notes, and snippets.

@TravisCardwell
Created July 22, 2020 12:30
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save TravisCardwell/bf3855c4488f8f636d130a44a1ef963a to your computer and use it in GitHub Desktop.
Save TravisCardwell/bf3855c4488f8f636d130a44a1ef963a to your computer and use it in GitHub Desktop.
demonstration of using template inheritance in ginger
#!/usr/bin/env stack
{- stack
script
--resolver lts-16.6
--package filepath
--package ginger
--package text
-}
-- This is a demonstration of using template inheritance in ginger.
--
-- * https://old.reddit.com/r/haskell/comments/hvoegk/web_development/
-- * https://hackage.haskell.org/package/ginger
-- * https://jinja.palletsprojects.com/en/2.11.x/
--
-- This file is a Stack script. With Stack installed, make this file
-- executable and execute it to run the script.
--
-- $ chmod 0755 GingerDemo.hs
-- $ ./GingerDemo.hs
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Main (main) where
-- https://hackage.haskell.org/package/base
import Data.Functor.Identity (Identity(runIdentity))
-- https://hackage.haskell.org/package/filepath
import qualified System.FilePath as FilePath
-- https://hackage.haskell.org/package/ginger
import qualified Text.Ginger as Ginger
import Text.Ginger.Html (htmlSource)
-- https://hackage.haskell.org/package/text
import Data.Text (Text)
import qualified Data.Text.IO as TIO
------------------------------------------------------------------------------
-- $Templates
--
-- To make the demo with a single file, the templates are defined within the
-- file.
-- The base template is the parent template.
baseTemplate :: String
baseTemplate = unlines
[ "<!DOCTYPE html>"
, "<html lang=\"en\">"
, "\t<head>"
, "\t\t<title>{% block title %}{% endblock %} - Ginger Demo</title>"
, "\t</head>"
, "\t<body>"
, "\t\t<main>"
, "{% block content %}{% endblock %}"
, "\t\t</main>"
, "\t\t<footer>"
, "{% include \"footer.html\" %}"
, "\t\t</footer>"
, "\t</body>"
, "</html>"
]
-- The child template extends the base template, demonstrating template
-- inheritance.
childTemplate :: String
childTemplate = unlines
[ "{% extends \"base.html\" %}"
, "{% block title %}Child{% endblock %}"
, "{% block content %}"
, "<h1>Child</h1>"
, "<p>Hello {{ name }}!</p>"
, "{% endblock %}"
]
-- The footer template is simply included by the base template.
footerTemplate :: String
footerTemplate = unlines
[ "<p>Public Domain</p>"
]
-- In actual projects, the include resolver is usually implemented using the
-- 'IO' monad, to load templates from the filesystem or a database. For this
-- demonstration, no IO is necessary, so it is implemented using the
-- 'Identity' monad.
pureIncludeResolver
:: Ginger.SourceName
-> Identity (Maybe Ginger.Source)
pureIncludeResolver source = pure $ case FilePath.takeFileName source of
"base.html" -> Just baseTemplate
"child.html" -> Just childTemplate
"footer.html" -> Just footerTemplate
_ -> Nothing
------------------------------------------------------------------------------
main :: IO ()
main = do
-- Loading the child template results in the following templates to be
-- resolved:
--
-- 1. child template
-- 2. base template, due to inheritance
-- 3. footer template, because it is included in the base template
template <- either (fail . Ginger.peErrorMessage) pure . runIdentity $
Ginger.parseGingerFile pureIncludeResolver "child.html"
-- Create a context to be used when rendering the template:
let context = Ginger.makeContextHtml $ \case
"name" -> Ginger.toGVal ("world" :: Text)
_ -> Ginger.toGVal ()
-- Use 'Ginger.runGinger' to render the template using the context. Since
-- a HTML context is used, the result is HTML, and 'htmlSource' renders
-- the HTML as 'Text'.
TIO.putStr . htmlSource $ Ginger.runGinger context template
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment