Skip to content

Commit

Permalink
Updating the docs & making everything prettier
Browse files Browse the repository at this point in the history
  • Loading branch information
Daniil Frumin committed Sep 15, 2013
1 parent 5f27ba9 commit 26c9b0d
Show file tree
Hide file tree
Showing 4 changed files with 124 additions and 43 deletions.
4 changes: 2 additions & 2 deletions LICENSE
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
Copyright (c) 2013, Dan Frumin
Copyright (c) 2013, Daniil Frumin

All rights reserved.

Expand All @@ -13,7 +13,7 @@ modification, are permitted provided that the following conditions are met:
disclaimer in the documentation and/or other materials provided
with the distribution.

* Neither the name of Dan Frumin nor the names of other
* Neither the name of Daniil Frumin nor the names of other
contributors may be used to endorse or promote products derived
from this software without specific prior written permission.

Expand Down
2 changes: 0 additions & 2 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,6 @@ Integrating Hastache to Scotty
- [Scotty](http://github.com/xich/scotty) - a light-weighted Web framework/router
- [Hastache](https://github.com/lymar/hastache) - Haskell implementation of [Mustache](http://mustache.github.io/) templates

This is still work-in-progress

```haskell
{-# LANGUAGE OverloadedStrings #-}
module Main where
Expand Down
15 changes: 11 additions & 4 deletions scotty-hastache.cabal
Original file line number Diff line number Diff line change
@@ -1,7 +1,15 @@
name: scotty-hastache
version: 0.1.0.0
synopsis: Easy Hastache templating support for Scotty
-- description:
version: 0.1.0
synopsis: Easy Mustache templating support for Scotty

description: This library provides a small templating DSL extension
for Scotty via the `hastache` library.
.
[Scotty] is a light-weighted Web framework\/router <http://hackage.haskell.org/package/scotty>
.
[Hashache] is a Haskell implementation of the Mustache templates: <http://mustache.github.io/>, <http://hackage.haskell.org/package/hastache>


license: BSD3
license-file: LICENSE
author: Dan Frumin
Expand Down Expand Up @@ -30,7 +38,6 @@ library
warp >= 1.3.4.1



hs-source-dirs: src
GHC-options: -Wall -fno-warn-orphans
default-language: Haskell2010
Expand Down
146 changes: 111 additions & 35 deletions src/Web/Scotty/Hastache.hs
Original file line number Diff line number Diff line change
@@ -1,76 +1,127 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ImpredicativeTypes #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE ImpredicativeTypes #-}

-- | Hastache templating for Scotty
{- | Hastache templating for Scotty
@
\{\-\# LANGUAGE OverloadedStrings \#\-\}
module Main where
import Text.Hastache
import Web.Scotty.Trans as S
import Web.Scotty.Hastache
main :: IO ()
main = scottyH 3000 $ do
setTemplatesDir \"templates\"
-- ^ Setting up the director with templates
get \"/:word\" $ do
beam <- param \"word\"
setH \"action\" $ MuVariable (beam :: String)
-- ^ \"action\" will be binded to the contents of \'beam\'
hastache \"greet.html\"
@
Given the following template:
@
\<h1\>Scotty, {{action}} me up!\<\/h1\>
@
Upon the @GET \/beam@ the result will be:
@
\<h1\>Scotty, beam me up!\<\/h1\>
@
-}
module Web.Scotty.Hastache where

import Control.Arrow ((***))
import Control.Monad.State as State
import Data.IORef (newIORef, readIORef,
writeIORef)
import qualified Data.Map as M
import Data.Maybe
import Data.IORef
import Data.Monoid
import Network.Wai
import Data.Maybe (fromMaybe)
import Data.Monoid (mempty)
import Network.Wai (Application, Response)
import Network.Wai.Handler.Warp (Port)
import System.FilePath.Posix
import System.FilePath.Posix ((</>))
import Text.Blaze.Html.Renderer.String as BRS
import Text.Blaze.Html.Renderer.Utf8 as BRU
import Text.Blaze.Internal
import Text.Blaze.Internal (Markup)
import Text.Hastache
import Text.Hastache.Context
import Web.Scotty.Trans as S

-- | State with Hastache config
type HState = StateT ((MuConfig IO, M.Map String (MuType IO))) IO

type ScottyH = ScottyT HState
type ActionH = ActionT HState

mkHStateRunners :: MuConfig IO -> IO (forall a. HState a -> IO a, HState Response -> IO Response)
mkHStateRunners conf = do
gstate <- newIORef undefined
let runH m = do
(r,(muconf,_)) <- runStateT m (conf, mempty)
writeIORef gstate muconf
return r
runActionToIO m = do
muconf <- readIORef gstate
evalStateT m (muconf, mempty)
return (runH, runActionToIO)
-- * Runners and types

-- | The runner to use instead of 'scotty'
scottyH :: Port -> ScottyH () -> IO ()
scottyH p s = do
(runH, runActionToIO) <- mkHStateRunners defaultConfig
scottyT p runH runActionToIO s

-- | The runner to use instead of 'scottyOpts'
scottyHOpts :: Options -> ScottyH () -> IO ()
scottyHOpts opts s = do
(runH, runActionToIO) <- mkHStateRunners defaultConfig
scottyOptsT opts runH runActionToIO s

scottyHApp :: MuConfig IO -> ScottyH () -> IO Application
scottyHApp conf defs = do
(runH, runActionToIO) <- mkHStateRunners conf
scottyAppT runH runActionToIO defs
-- | A type synonym for @ScottyT HState@
type ScottyH = ScottyT HState

setTemplatesDir :: FilePath -> ScottyH ()
setTemplatesDir dir = do
(conf :: MuConfig IO, tmap) <- lift State.get
lift . State.put $ (conf { muTemplateFileDir = Just dir }, tmap)
-- | A type synonym for @ScottyT HState@
type ActionH = ActionT HState

-- * The DSL itself

-- ** Configuration

-- | Update the Hastache configuration as whole
setHastacheConfig :: MuConfig IO -> ScottyH ()
setHastacheConfig conf = do
(_, tmap) <- lift State.get
lift . State.put $ (conf, tmap)

-- | Modify the Hastache configuration as whole
modifyHastacheConfig :: (MuConfig IO -> MuConfig IO) -> ScottyH ()
modifyHastacheConfig f = lift $ State.modify (f *** id)

-- | Set the path to the directory with templates. This affects
-- how /both/ 'hastache' and the @{{> template}}@ bit searches for the
-- template files.
setTemplatesDir :: FilePath -> ScottyH ()
setTemplatesDir dir = do
lift $ State.modify $ \(conf :: MuConfig IO, tmap) ->
(conf { muTemplateFileDir = Just dir }, tmap)

-- | Set the default extension for template files. This affects
-- how /both/ 'hastache' and the @{{> template}}@ bit searches for the
-- template files.
setTemplateFileExt :: String -> ScottyH ()
setTemplateFileExt ext = do
lift $ State.modify $ \(conf :: MuConfig IO, tmap) ->
(conf { muTemplateFileExt = Just ext }, tmap)

-- ** Actions

-- | This is a function, just like 'S.html' or 'S.text'.
-- It takes a name of the template (the path is computed using the
-- information about the templates dir and template files extension)
-- and renders it using Hastache.
--
-- The variables that have been initialized using 'setH' are
-- substituted for their values, uninitialized variables are
-- considered to be empty/null.
hastache :: FilePath -> ActionT HState ()
hastache tpl = do
((conf :: MuConfig IO), tmap) <- lift State.get
(conf :: MuConfig IO, tmap) <- lift State.get
header "Content-Type" "text/html"
let cntx a = fromMaybe MuNothing (M.lookup a tmap)
let tplFile = fromMaybe "." (muTemplateFileDir conf)
Expand All @@ -79,11 +130,36 @@ hastache tpl = do
res <- liftIO $ hastacheFile conf tplFile (mkStrContext cntx)
raw res

-- | Set the value of a mustache variable.
setH :: String -> MuType IO -> ActionT HState ()
setH x y = do
(conf, tmap) <- lift State.get
lift . State.put $ (conf, M.insert x y tmap)

-- * Internals

-- | State with the Hastache config
type HState = StateT (MuConfig IO, M.Map String (MuType IO)) IO

mkHStateRunners :: MuConfig IO -> IO (forall a. HState a -> IO a, HState Response -> IO Response)
mkHStateRunners conf = do
gstate <- newIORef undefined
let runH m = do
(r,(muconf,_)) <- runStateT m (conf, mempty)
writeIORef gstate muconf
return r
runActionToIO m = do
muconf <- readIORef gstate
evalStateT m (muconf, mempty)
return (runH, runActionToIO)

scottyHApp :: MuConfig IO -> ScottyH () -> IO Application
scottyHApp conf defs = do
(runH, runActionToIO) <- mkHStateRunners conf
scottyAppT runH runActionToIO defs

-- * Orphans

instance Show Markup where
show = BRS.renderHtml

Expand Down

0 comments on commit 26c9b0d

Please sign in to comment.