use widgetFile

This commit is contained in:
Joey Hess 2012-07-26 22:54:31 -04:00
parent e40f94cbcd
commit 615dc09ffc
2 changed files with 8 additions and 14 deletions

View file

@ -21,7 +21,6 @@ import Git
import Yesod import Yesod
import Yesod.Static import Yesod.Static
import Text.Hamlet import Text.Hamlet
import Text.Julius
import Network.Socket (PortNumber) import Network.Socket (PortNumber)
import Text.Blaze.Renderer.String import Text.Blaze.Renderer.String
import Data.Text import Data.Text
@ -90,7 +89,7 @@ autoUpdate poll gethtml home ms_delay ms_startdelay = do
let delay = show ms_delay let delay = show ms_delay
let startdelay = show ms_startdelay let startdelay = show ms_startdelay
addScriptRemote "http://ajax.googleapis.com/ajax/libs/jquery/1.6.2/jquery.min.js" addScriptRemote "http://ajax.googleapis.com/ajax/libs/jquery/1.6.2/jquery.min.js"
toWidgetHead $(juliusFile $ juliusTemplate "longpolling") $(widgetFile "longpolling")
where where
ms_to_seconds :: Int -> Int ms_to_seconds :: Int -> Int
ms_to_seconds ms = ceiling ((fromIntegral ms :: Double) / 1000) ms_to_seconds ms = ceiling ((fromIntegral ms :: Double) / 1000)
@ -102,7 +101,7 @@ statusDisplay = do
time <- show <$> liftIO getCurrentTime time <- show <$> liftIO getCurrentTime
poll <- lift newIdent poll <- lift newIdent
$(whamletFile $ hamletTemplate "status") $(widgetFile "status")
autoUpdate poll StatusR HomeR (3000 :: Int) (40 :: Int) autoUpdate poll StatusR HomeR (3000 :: Int) (40 :: Int)

View file

@ -1,4 +1,4 @@
{- Yesod stuff {- Yesod stuff, that's typically found in the scaffolded site.
- -
- Copyright 2012 Joey Hess <joey@kitenet.net> - Copyright 2012 Joey Hess <joey@kitenet.net>
- -
@ -7,16 +7,11 @@
module Utility.Yesod where module Utility.Yesod where
import System.FilePath import Yesod.Default.Util
import Language.Haskell.TH.Syntax
{- Filename of a template, in the templates/ directory. -} widgetFile :: String -> Q Exp
template :: FilePath -> FilePath widgetFile = widgetFileNoReload
template f = "templates" </> f
{- A hamlet template file. -}
hamletTemplate :: FilePath -> FilePath hamletTemplate :: FilePath -> FilePath
hamletTemplate f = template f ++ ".hamlet" hamletTemplate f = globFile "hamlet" f
{- A julius template file. -}
juliusTemplate :: FilePath -> FilePath
juliusTemplate f = template f ++ ".julius"