[web-devel] Re: Runtime Hamlet template parsing/rendering
Simon Michael
simon at joyful.com
Thu Aug 5 20:13:42 EDT 2010
On 8/5/10 12:57 AM, Michael Snoyman wrote:
> Thanks for the input everyone. I've just pushed the new Hamlet runtime code to github[1]. Instead of using data-object,
> I've created a new datatype: HamletData[2]. Runtime templates support *almost* the entirety of valid Hamlet documents;
Excellent! With the following kludgery I was able to change hamlet files and see the effect immediately. A boon for
development. Useful parse errors in the browser too. It's not all smooth of course. Including other hamlets and
integrating RT and non-RT hamlets seems a lot of work.
...
import Yesod hiding (defaultHamletSettings)
import Control.Failure
import Text.Hamlet.Parse (defaultHamletSettings)
import Text.Hamlet.RT
stringToHamletRT :: Failure HamletException m => String -> m HamletRT
stringToHamletRT s = parseHamletRT defaultHamletSettings s
hamletRTToHtml :: Failure HamletException m => HamletData HledgerWebAppRoute -> HamletRT -> m (Html ())
hamletRTToHtml d h = renderHamletRT h d show
instance Failure HamletException (Handler HledgerWebApp)
where failure = error . show
getAddformRT :: Handler HledgerWebApp RepHtml
getAddformRT = do
...
dir <- appWebdir `fmap` getYesod
addform <- liftIO $ readFile $ dir </> "addform.hamlet"
-- addform uses the transactionfields template
-- tfieldstmpl <- liftIO $ readFile $ dir </> "addformtransactionfields.hamlet"
-- tfields1 <- stringToHamletRT tfieldstmpl >>= hamletRTToHtml
-- (HDMap [("label", HDHtml $ string "To account")
-- ,("accthelp", HDHtml $ string "eg: expenses:food")
-- ,("amtfield", HDHtml $ preEscapedString $ printf "")
-- ...urgh
-- tfields1 <- hamletToHamletRT $ transactionfields 1
-- tfields2 <- hamletToHamletRT $ transactionfields 2
-- ...urgh
tfields1 <- stringToHamletRT ""
tfields2 <- stringToHamletRT ""
h <- stringToHamletRT addform >>= hamletRTToHtml
(HDMap [("date", HDHtml $ string "today")
,("desc", HDHtml $ string "")
,("datehelp", HDHtml $ string "eg: 7/20, 2010/1/1")
,("deschelp", HDHtml $ string "eg: supermarket (optional)")
,("transactionfields1", HDTemplate tfields1)
,("transactionfields2", HDTemplate tfields2)
])
hamletToRepHtml $ pageLayout td [$hamlet|$h$|]
More information about the web-devel
mailing list