web: move code to Hledger.Web for importability, consistency

This commit is contained in:
Simon Michael 2011-08-05 23:55:57 +00:00
parent d1447c984a
commit cd0c945454
9 changed files with 69 additions and 40 deletions

View File

@ -0,0 +1,33 @@
{-|
Re-export the modules of the hledger-web program.
-}
module Hledger.Web (
module Hledger.Web.App,
module Hledger.Web.AppRun,
module Hledger.Web.EmbeddedFiles,
module Hledger.Web.Handlers,
module Hledger.Web.Settings,
module Hledger.Web.StaticFiles,
tests_Hledger_Web
)
where
import Test.HUnit
import Hledger.Web.App
import Hledger.Web.AppRun
import Hledger.Web.EmbeddedFiles
import Hledger.Web.Handlers
import Hledger.Web.Settings
import Hledger.Web.StaticFiles
tests_Hledger_Web :: Test
tests_Hledger_Web = TestList
[
-- tests_Hledger_Web_App
-- ,tests_Hledger_Web_AppRun
-- ,tests_Hledger_Web_EmbeddedFiles
-- ,tests_Hledger_Web_Handlers
-- ,tests_Hledger_Web_Settings
-- ,tests_Hledger_Web_StaticFiles
]

View File

@ -1,13 +1,12 @@
{-# LANGUAGE QuasiQuotes, TemplateHaskell, TypeFamilies #-}
{-# LANGUAGE OverloadedStrings #-}
module App
module Hledger.Web.App
( App (..)
, AppRoute (..)
, resourcesApp
, Handler
, Widget
, module Yesod.Core
, module Settings
, StaticRoute (..)
, lift
, liftIO
@ -25,9 +24,8 @@ import Yesod.Helpers.Static
import Hledger.Cli.Options
import Hledger.Data
import Settings
import StaticFiles
import Hledger.Web.Settings
import Hledger.Web.StaticFiles
-- | The site argument for your application. This can be a good place to
-- keep settings and values requiring initialization before your application
@ -111,7 +109,7 @@ instance Yesod App where
-- users receiving stale content.
addStaticContent ext' _ content = do
let fn = base64md5 content ++ '.' : T.unpack ext'
let statictmp = Settings.staticdir ++ "/tmp/"
let statictmp = Hledger.Web.Settings.staticdir ++ "/tmp/"
liftIO $ createDirectoryIfMissing True statictmp
let fn' = statictmp ++ fn
exists <- liftIO $ doesFileExist fn'

View File

@ -2,7 +2,7 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module AppRun (
module Hledger.Web.AppRun (
withApp
,withDevelApp
,withWaiHandlerDevelApp
@ -16,10 +16,9 @@ import Yesod.Helpers.Static
import Hledger
import Hledger.Cli
import App
import Handlers
import Settings
import Hledger.Web.App
import Hledger.Web.Handlers
import Hledger.Web.Settings
-- This line actually creates our YesodSite instance. It is the second half
-- of the call to mkYesodData which occurs in App.hs. Please see
@ -37,8 +36,8 @@ withApp a f = toWaiApp a >>= f
withDevelApp :: Dynamic
withDevelApp = toDyn (withApp a :: (Application -> IO ()) -> IO ())
where a = App{
getStatic=static Settings.staticdir
,appRoot=Settings.defapproot
getStatic=static Hledger.Web.Settings.staticdir
,appRoot=Hledger.Web.Settings.defapproot
,appOpts=[]
,appArgs=[]
,appJournal=nulljournal
@ -52,7 +51,7 @@ withWaiHandlerDevelApp func = do
ej <- readJournalFile Nothing f
let Right j = ej
let a = App{
getStatic=static Settings.staticdir
getStatic=static Hledger.Web.Settings.staticdir
,appRoot=Settings.defapproot
,appOpts=[File f]
,appArgs=[]

View File

@ -8,7 +8,7 @@ startup, when needed. This simplifies installation for end-users, and
customisation too.
-}
module EmbeddedFiles
module Hledger.Web.EmbeddedFiles
(
files
,createFilesIfMissing
@ -20,7 +20,7 @@ import Data.FileEmbed (embedDir)
import System.Directory
import System.FilePath
import Settings (datadir)
import Hledger.Web.Settings (datadir)
-- | An embedded copy of all files below the the hledger-web data
-- directory (@.hledger/web/@) at compile time, as (FilePath,ByteString)

View File

@ -5,7 +5,7 @@ hledger-web's request handlers, and helpers.
-}
module Handlers where
module Hledger.Web.Handlers where
import Control.Applicative ((<$>), (<*>))
import Data.Aeson
@ -28,13 +28,12 @@ import Yesod.Json
import Hledger hiding (today)
import Hledger.Cli
import App
import Settings
import Hledger.Web.App
import Hledger.Web.Settings
getFaviconR :: Handler ()
getFaviconR = sendFile "image/x-icon" $ Settings.staticdir </> "favicon.ico"
getFaviconR = sendFile "image/x-icon" $ Hledger.Web.Settings.staticdir </> "favicon.ico"
getRobotsR :: Handler RepPlain
getRobotsR = return $ RepPlain $ toContent ("User-agent: *" :: ByteString)

View File

@ -8,7 +8,7 @@
-- In addition, you can configure a number of different aspects of Yesod
-- by overriding methods in the Yesod typeclass. That instance is
-- declared in the hledger-web.hs file.
module Settings
module Hledger.Web.Settings
( hamletFile
, cassiusFile
, juliusFile

View File

@ -9,10 +9,10 @@ way; use their FilePath or URL to access them.
This is a separate module to satisfy template haskell requirements.
-}
module StaticFiles where
module Hledger.Web.StaticFiles where
import Yesod.Helpers.Static
import Settings (staticdir)
import Hledger.Web.Settings (staticdir)
$(staticFiles staticdir)

View File

@ -51,15 +51,17 @@ executable hledger-web
else
ghc-options: -W -threaded
other-modules:
App
EmbeddedFiles
Settings
StaticFiles
Handlers
Hledger.Web
Hledger.Web.App
Hledger.Web.AppRun
Hledger.Web.EmbeddedFiles
Hledger.Web.Settings
Hledger.Web.StaticFiles
Hledger.Web.Handlers
build-depends:
hledger == 0.15
,hledger-lib == 0.15
-- ,HUnit
,HUnit
,base >= 4 && < 5
,bytestring
-- ,containers
@ -103,10 +105,11 @@ library
else
Buildable: False
exposed-modules:
AppRun
Hledger.Web.AppRun
other-modules:
App
EmbeddedFiles
Settings
StaticFiles
Handlers
Hledger.Web
Hledger.Web.App
Hledger.Web.EmbeddedFiles
Hledger.Web.Settings
Hledger.Web.StaticFiles
Hledger.Web.Handlers

View File

@ -26,10 +26,7 @@ import Hledger.Cli
import Hledger.Data
import Prelude hiding (putStr, putStrLn)
import Hledger.Utils.UTF8 (putStr, putStrLn)
import App
import AppRun (withApp)
import EmbeddedFiles (createFilesIfMissing)
import Hledger.Web
progname_web = progname_cli ++ "-web"