Background: I am studying how Hamlet works, with WAI, but without Yesod. I have no grasp of Template Haskell, but before I dive into it, I am wondering if there is a known/quick solution for this task.
Specifics: I would like to know how to change the NewlineStyle in the context of a Hamlet quasiquote.
Exploration: I believe it has something to do with a function call that looks like this
hamletWithSettings
htmlRules
HamletSettings
{
hamletDoctype = "<!DOCTYPE html>"
,hamletNewlines = DefaultNewlineStyle
,Hamlet.hamletCloseStyle = htmlCloseStyle -- this fn is in a hidden module
,Hamlet.hamletDoctypeNames = []
}
... however, I don't know how to write the code that does this, in the context of the quasiquote.
Here is the working code, which I hope to modify:
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
import Control.Monad.Trans.Resource
import Text.Hamlet as Hamlet
import qualified Data.ByteString.Lazy.Char8 as ByteString
import qualified Network.Wai as Wai
import qualified Network.HTTP.Types as Http
import qualified Network.Wai.Handler.Warp as Warp
import qualified Text.Blaze as Blaze
import qualified Text.Blaze.Html.Renderer.String as Blaze
-------------------------------------------------------------------------------
main :: IO ()
main = Warp.run 3000 application
-------------------------------------------------------------------------------
application :: Wai.Request -> ResourceT IO Wai.Response
application request = return $
case (head $ Wai.pathInfo request) of
"html" ->
Wai.responseLBS Http.status200 [] $ ByteString.pack
$ Blaze.renderHtml
$ htmlDoc -- defined below
"d3" ->
Wai.ResponseFile Http.status200 [] "./d3.v2.min.js" Nothing
_ ->
Wai.responseLBS Http.status400 [] ""
-------------------------------------------------------------------------------
htmlDoc :: Hamlet.Html
htmlDoc = [shamlet|
!!!
<html>
<head>
<title>Study Graph
<!-- <link rel="stylesheet" type="text/css" href="/css"> -->
<script type="text/javascript" src="/d3" />
<style>
<script>
window.onload = function()
{
svg =
d3 .select("body")
.append("svg")
.attr("width", "100%")
.attr("height", "100%")
/* SOLUTION to strawman: a solitary "\" on this code row, will render a single newline character; i.e. "\n\\\n" renders as "\n" */
svg .selectAll("circle")
.data([ {"cx": 1.0, "cy": 1.1, "r":1},
{"cx": 2.0, "cy": 2.5, "r":0.9} ])
}
<body>
|]
-------------------------------------------------------------------------------
Thanks in advance for any assistance, insults, or other commentary.
The basic idea would be to create a new identifier, e.g.:
myHamlet = hamletWithSettings
htmlRules
( HamletSettings
"<!DOCTYPE html>"
DefaultNewlineStyle htmlCloseStyle doctypeNames )
Then use myHamlet
in place of hamlet
, e.g.:
htmlDoc = [myHamlet|...|]
Due to the stage restriction, you'll likely need to declare myHamlet
in a different module to the one where you use it.