web: Conform layout to the rest of hledger-* packages
This commit is contained in:
parent
af98eecdf8
commit
e8668e2a5c
@ -4,27 +4,26 @@
|
|||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
{-# LANGUAGE ViewPatterns #-}
|
{-# LANGUAGE ViewPatterns #-}
|
||||||
|
|
||||||
module Application
|
module Hledger.Web.Application
|
||||||
( makeApplication
|
( makeApplication
|
||||||
, makeFoundation
|
, makeFoundation
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Import
|
|
||||||
|
|
||||||
import Data.IORef (newIORef, writeIORef)
|
import Data.IORef (newIORef, writeIORef)
|
||||||
import Network.Wai.Middleware.RequestLogger (logStdoutDev, logStdout)
|
import Network.Wai.Middleware.RequestLogger (logStdoutDev, logStdout)
|
||||||
import Network.HTTP.Client (defaultManagerSettings)
|
import Network.HTTP.Client (defaultManagerSettings)
|
||||||
import Network.HTTP.Conduit (newManager)
|
import Network.HTTP.Conduit (newManager)
|
||||||
import Yesod.Default.Config
|
import Yesod.Default.Config
|
||||||
|
|
||||||
import Handler.AddR (getAddR, postAddR)
|
|
||||||
import Handler.Common
|
|
||||||
(getDownloadR, getFaviconR, getManageR, getRobotsR, getRootR)
|
|
||||||
import Handler.EditR (getEditR, postEditR)
|
|
||||||
import Handler.UploadR (getUploadR, postUploadR)
|
|
||||||
import Handler.JournalR (getJournalR)
|
|
||||||
import Handler.RegisterR (getRegisterR)
|
|
||||||
import Hledger.Data (Journal, nulljournal)
|
import Hledger.Data (Journal, nulljournal)
|
||||||
|
import Hledger.Web.Handler.AddR (getAddR, postAddR)
|
||||||
|
import Hledger.Web.Handler.Common
|
||||||
|
(getDownloadR, getFaviconR, getManageR, getRobotsR, getRootR)
|
||||||
|
import Hledger.Web.Handler.EditR (getEditR, postEditR)
|
||||||
|
import Hledger.Web.Handler.UploadR (getUploadR, postUploadR)
|
||||||
|
import Hledger.Web.Handler.JournalR (getJournalR)
|
||||||
|
import Hledger.Web.Handler.RegisterR (getRegisterR)
|
||||||
|
import Hledger.Web.Import
|
||||||
import Hledger.Web.WebOptions (WebOpts(serve_))
|
import Hledger.Web.WebOptions (WebOpts(serve_))
|
||||||
|
|
||||||
-- This line actually creates our YesodDispatch instance. It is the second half
|
-- This line actually creates our YesodDispatch instance. It is the second half
|
||||||
@ -14,7 +14,7 @@
|
|||||||
-- | Define the web application's foundation, in the usual Yesod style.
|
-- | Define the web application's foundation, in the usual Yesod style.
|
||||||
-- See a default Yesod app's comments for more details of each part.
|
-- See a default Yesod app's comments for more details of each part.
|
||||||
|
|
||||||
module Foundation where
|
module Hledger.Web.Foundation where
|
||||||
|
|
||||||
import Control.Monad (join)
|
import Control.Monad (join)
|
||||||
import qualified Data.ByteString.Char8 as BC
|
import qualified Data.ByteString.Char8 as BC
|
||||||
@ -34,19 +34,18 @@ import Yesod
|
|||||||
import Yesod.Static
|
import Yesod.Static
|
||||||
import Yesod.Default.Config
|
import Yesod.Default.Config
|
||||||
|
|
||||||
import Settings (Extra(..), widgetFile)
|
|
||||||
import Settings.StaticFiles
|
|
||||||
import Widget.Common (balanceReportAsHtml)
|
|
||||||
|
|
||||||
#ifndef DEVELOPMENT
|
#ifndef DEVELOPMENT
|
||||||
import Settings (staticDir)
|
import Hledger.Web.Settings (staticDir)
|
||||||
import Text.Jasmine (minifym)
|
import Text.Jasmine (minifym)
|
||||||
import Yesod.Default.Util (addStaticContentExternal)
|
import Yesod.Default.Util (addStaticContentExternal)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
import Hledger
|
import Hledger
|
||||||
import Hledger.Cli (CliOpts(..), journalReloadIfChanged)
|
import Hledger.Cli (CliOpts(..), journalReloadIfChanged)
|
||||||
|
import Hledger.Web.Settings (Extra(..), widgetFile)
|
||||||
|
import Hledger.Web.Settings.StaticFiles
|
||||||
import Hledger.Web.WebOptions
|
import Hledger.Web.WebOptions
|
||||||
|
import Hledger.Web.Widget.Common (balanceReportAsHtml)
|
||||||
|
|
||||||
-- | The site argument for your application. This can be a good place to
|
-- | The site argument for your application. This can be a good place to
|
||||||
-- keep settings and values requiring initialization before your application
|
-- keep settings and values requiring initialization before your application
|
||||||
@ -154,7 +153,7 @@ instance Yesod App where
|
|||||||
-- and names them based on a hash of their content. This allows
|
-- and names them based on a hash of their content. This allows
|
||||||
-- expiration dates to be set far in the future without worry of
|
-- expiration dates to be set far in the future without worry of
|
||||||
-- users receiving stale content.
|
-- users receiving stale content.
|
||||||
addStaticContent = addStaticContentExternal minifym base64md5 Settings.staticDir (StaticR . flip StaticRoute [])
|
addStaticContent = addStaticContentExternal minifym base64md5 staticDir (StaticR . flip StaticRoute [])
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
-- This instance is required to use forms. You can modify renderMessage to
|
-- This instance is required to use forms. You can modify renderMessage to
|
||||||
@ -4,17 +4,16 @@
|
|||||||
{-# LANGUAGE QuasiQuotes #-}
|
{-# LANGUAGE QuasiQuotes #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
|
|
||||||
module Handler.AddR
|
module Hledger.Web.Handler.AddR
|
||||||
( getAddR
|
( getAddR
|
||||||
, postAddR
|
, postAddR
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Import
|
|
||||||
|
|
||||||
import Hledger
|
import Hledger
|
||||||
import Hledger.Cli.Commands.Add (appendToJournalFileOrStdout)
|
import Hledger.Cli.Commands.Add (appendToJournalFileOrStdout)
|
||||||
import Widget.AddForm (addForm)
|
import Hledger.Web.Import
|
||||||
import Widget.Common (fromFormSuccess)
|
import Hledger.Web.Widget.AddForm (addForm)
|
||||||
|
import Hledger.Web.Widget.Common (fromFormSuccess)
|
||||||
|
|
||||||
getAddR :: Handler ()
|
getAddR :: Handler ()
|
||||||
getAddR = postAddR
|
getAddR = postAddR
|
||||||
@ -3,7 +3,7 @@
|
|||||||
{-# LANGUAGE QuasiQuotes #-}
|
{-# LANGUAGE QuasiQuotes #-}
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
|
|
||||||
module Handler.Common
|
module Hledger.Web.Handler.Common
|
||||||
( getDownloadR
|
( getDownloadR
|
||||||
, getFaviconR
|
, getFaviconR
|
||||||
, getManageR
|
, getManageR
|
||||||
@ -11,13 +11,12 @@ module Handler.Common
|
|||||||
, getRootR
|
, getRootR
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Import
|
|
||||||
|
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import Yesod.Default.Handlers (getFaviconR, getRobotsR)
|
import Yesod.Default.Handlers (getFaviconR, getRobotsR)
|
||||||
|
|
||||||
import Hledger (jfiles)
|
import Hledger (jfiles)
|
||||||
import Widget.Common (journalFile404)
|
import Hledger.Web.Import
|
||||||
|
import Hledger.Web.Widget.Common (journalFile404)
|
||||||
|
|
||||||
getRootR :: Handler Html
|
getRootR :: Handler Html
|
||||||
getRootR = redirect JournalR
|
getRootR = redirect JournalR
|
||||||
@ -5,14 +5,14 @@
|
|||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
|
|
||||||
module Handler.EditR
|
module Hledger.Web.Handler.EditR
|
||||||
( getEditR
|
( getEditR
|
||||||
, postEditR
|
, postEditR
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Import
|
import Hledger.Web.Import
|
||||||
|
import Hledger.Web.Widget.Common
|
||||||
import Widget.Common (fromFormSuccess, helplink, journalFile404, writeValidJournal)
|
(fromFormSuccess, helplink, journalFile404, writeValidJournal)
|
||||||
|
|
||||||
editForm :: FilePath -> Text -> Markup -> MForm Handler (FormResult Text, Widget)
|
editForm :: FilePath -> Text -> Markup -> MForm Handler (FormResult Text, Widget)
|
||||||
editForm f txt =
|
editForm f txt =
|
||||||
@ -5,15 +5,14 @@
|
|||||||
{-# LANGUAGE QuasiQuotes #-}
|
{-# LANGUAGE QuasiQuotes #-}
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
|
|
||||||
module Handler.JournalR where
|
module Hledger.Web.Handler.JournalR where
|
||||||
|
|
||||||
import Import
|
|
||||||
|
|
||||||
import Hledger
|
import Hledger
|
||||||
import Hledger.Cli.CliOptions
|
import Hledger.Cli.CliOptions
|
||||||
|
import Hledger.Web.Import
|
||||||
import Hledger.Web.WebOptions
|
import Hledger.Web.WebOptions
|
||||||
import Widget.AddForm (addModal)
|
import Hledger.Web.Widget.AddForm (addModal)
|
||||||
import Widget.Common (accountQuery, mixedAmountAsHtml)
|
import Hledger.Web.Widget.Common (accountQuery, mixedAmountAsHtml)
|
||||||
|
|
||||||
-- | The formatted journal view, with sidebar.
|
-- | The formatted journal view, with sidebar.
|
||||||
-- XXX like registerReportAsHtml
|
-- XXX like registerReportAsHtml
|
||||||
@ -6,9 +6,7 @@
|
|||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
|
|
||||||
module Handler.RegisterR where
|
module Hledger.Web.Handler.RegisterR where
|
||||||
|
|
||||||
import Import
|
|
||||||
|
|
||||||
import Data.List (intersperse)
|
import Data.List (intersperse)
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
@ -16,9 +14,10 @@ import Text.Hamlet (hamletFile)
|
|||||||
|
|
||||||
import Hledger
|
import Hledger
|
||||||
import Hledger.Cli.CliOptions
|
import Hledger.Cli.CliOptions
|
||||||
|
import Hledger.Web.Import
|
||||||
import Hledger.Web.WebOptions
|
import Hledger.Web.WebOptions
|
||||||
import Widget.AddForm (addModal)
|
import Hledger.Web.Widget.AddForm (addModal)
|
||||||
import Widget.Common (mixedAmountAsHtml)
|
import Hledger.Web.Widget.Common (mixedAmountAsHtml)
|
||||||
|
|
||||||
-- | The main journal/account register view, with accounts sidebar.
|
-- | The main journal/account register view, with accounts sidebar.
|
||||||
getRegisterR :: Handler Html
|
getRegisterR :: Handler Html
|
||||||
@ -4,19 +4,18 @@
|
|||||||
{-# LANGUAGE QuasiQuotes #-}
|
{-# LANGUAGE QuasiQuotes #-}
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
|
|
||||||
module Handler.UploadR
|
module Hledger.Web.Handler.UploadR
|
||||||
( getUploadR
|
( getUploadR
|
||||||
, postUploadR
|
, postUploadR
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Import
|
|
||||||
|
|
||||||
import qualified Data.ByteString.Lazy as BL
|
import qualified Data.ByteString.Lazy as BL
|
||||||
import Data.Conduit (connect)
|
import Data.Conduit (connect)
|
||||||
import Data.Conduit.Binary (sinkLbs)
|
import Data.Conduit.Binary (sinkLbs)
|
||||||
import qualified Data.Text.Encoding as TE
|
import qualified Data.Text.Encoding as TE
|
||||||
|
|
||||||
import Widget.Common (fromFormSuccess, journalFile404, writeValidJournal)
|
import Hledger.Web.Import
|
||||||
|
import Hledger.Web.Widget.Common (fromFormSuccess, journalFile404, writeValidJournal)
|
||||||
|
|
||||||
uploadForm :: FilePath -> Markup -> MForm Handler (FormResult FileInfo, Widget)
|
uploadForm :: FilePath -> Markup -> MForm Handler (FormResult FileInfo, Widget)
|
||||||
uploadForm f =
|
uploadForm f =
|
||||||
@ -1,5 +1,5 @@
|
|||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
module Import
|
module Hledger.Web.Import
|
||||||
( module Import
|
( module Import
|
||||||
) where
|
) where
|
||||||
|
|
||||||
@ -21,10 +21,9 @@ import Data.Traversable as Import
|
|||||||
import Data.Void as Import (Void)
|
import Data.Void as Import (Void)
|
||||||
import Text.Blaze as Import (Markup)
|
import Text.Blaze as Import (Markup)
|
||||||
|
|
||||||
import Foundation as Import
|
import Hledger.Web.Foundation as Import
|
||||||
import Settings as Import
|
import Hledger.Web.Settings as Import
|
||||||
import Settings.Development as Import
|
import Hledger.Web.Settings.StaticFiles as Import
|
||||||
import Settings.StaticFiles as Import
|
|
||||||
|
|
||||||
#if !(MIN_VERSION_base(4,11,0))
|
#if !(MIN_VERSION_base(4,11,0))
|
||||||
import Data.Monoid as Import ((<>))
|
import Data.Monoid as Import ((<>))
|
||||||
@ -25,13 +25,12 @@ import Text.Printf (printf)
|
|||||||
import Yesod.Default.Config
|
import Yesod.Default.Config
|
||||||
import Yesod.Default.Main (defaultDevelApp)
|
import Yesod.Default.Main (defaultDevelApp)
|
||||||
|
|
||||||
import Application (makeApplication)
|
|
||||||
import Settings (Extra(..), parseExtra)
|
|
||||||
|
|
||||||
import Hledger
|
import Hledger
|
||||||
import Hledger.Cli hiding (progname,prognameandversion)
|
import Hledger.Cli hiding (progname,prognameandversion)
|
||||||
import Hledger.Cli.Utils (journalTransform)
|
import Hledger.Cli.Utils (journalTransform)
|
||||||
import Hledger.Utils.UTF8IOCompat (putStrLn)
|
import Hledger.Utils.UTF8IOCompat (putStrLn)
|
||||||
|
import Hledger.Web.Application (makeApplication)
|
||||||
|
import Hledger.Web.Settings (Extra(..), parseExtra)
|
||||||
import Hledger.Web.WebOptions
|
import Hledger.Web.WebOptions
|
||||||
|
|
||||||
|
|
||||||
@ -4,7 +4,7 @@
|
|||||||
-- In addition, you can configure a number of different aspects of Yesod
|
-- In addition, you can configure a number of different aspects of Yesod
|
||||||
-- by overriding methods in the Yesod typeclass. That instance is
|
-- by overriding methods in the Yesod typeclass. That instance is
|
||||||
-- declared in the Foundation.hs file.
|
-- declared in the Foundation.hs file.
|
||||||
module Settings where
|
module Hledger.Web.Settings where
|
||||||
|
|
||||||
import Data.Default (def)
|
import Data.Default (def)
|
||||||
import Data.Semigroup ((<>))
|
import Data.Semigroup ((<>))
|
||||||
@ -16,8 +16,16 @@ import Text.Shakespeare.Text (st)
|
|||||||
import Yesod.Default.Config
|
import Yesod.Default.Config
|
||||||
import Yesod.Default.Util
|
import Yesod.Default.Util
|
||||||
|
|
||||||
import Settings.Development
|
development :: Bool
|
||||||
|
development =
|
||||||
|
#if DEVELOPMENT
|
||||||
|
True
|
||||||
|
#else
|
||||||
|
False
|
||||||
|
#endif
|
||||||
|
|
||||||
|
production :: Bool
|
||||||
|
production = not development
|
||||||
|
|
||||||
hledgerorgurl :: Text
|
hledgerorgurl :: Text
|
||||||
hledgerorgurl = "http://hledger.org"
|
hledgerorgurl = "http://hledger.org"
|
||||||
@ -1,11 +1,10 @@
|
|||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
module Settings.StaticFiles where
|
module Hledger.Web.Settings.StaticFiles where
|
||||||
|
|
||||||
import System.IO (stdout, hFlush)
|
import System.IO (stdout, hFlush)
|
||||||
import Yesod.Static (Static, embed, publicFiles, staticDevel)
|
import Yesod.Static (Static, embed, publicFiles, staticDevel)
|
||||||
|
|
||||||
import Settings (staticDir)
|
import Hledger.Web.Settings (staticDir, development)
|
||||||
import Settings.Development (development)
|
|
||||||
|
|
||||||
-- | use this to create your static file serving site
|
-- | use this to create your static file serving site
|
||||||
-- staticSite :: IO Static.Static
|
-- staticSite :: IO Static.Static
|
||||||
@ -12,9 +12,8 @@ import qualified Data.Text as T
|
|||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import System.Environment (getArgs)
|
import System.Environment (getArgs)
|
||||||
|
|
||||||
import Settings (defhost, defport, defbaseurl)
|
|
||||||
|
|
||||||
import Hledger.Cli hiding (progname, version)
|
import Hledger.Cli hiding (progname, version)
|
||||||
|
import Hledger.Web.Settings (defhost, defport, defbaseurl)
|
||||||
|
|
||||||
progname, version :: String
|
progname, version :: String
|
||||||
progname = "hledger-web"
|
progname = "hledger-web"
|
||||||
@ -5,7 +5,7 @@
|
|||||||
{-# LANGUAGE RankNTypes #-}
|
{-# LANGUAGE RankNTypes #-}
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
|
|
||||||
module Widget.AddForm
|
module Hledger.Web.Widget.AddForm
|
||||||
( addForm
|
( addForm
|
||||||
, addModal
|
, addModal
|
||||||
) where
|
) where
|
||||||
@ -24,7 +24,7 @@ import Text.Megaparsec (eof, parseErrorPretty, runParser)
|
|||||||
import Yesod
|
import Yesod
|
||||||
|
|
||||||
import Hledger
|
import Hledger
|
||||||
import Settings (widgetFile)
|
import Hledger.Web.Settings (widgetFile)
|
||||||
|
|
||||||
-- XXX <select> which journal to add to
|
-- XXX <select> which journal to add to
|
||||||
|
|
||||||
@ -4,7 +4,7 @@
|
|||||||
{-# LANGUAGE QuasiQuotes #-}
|
{-# LANGUAGE QuasiQuotes #-}
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
|
|
||||||
module Widget.Common
|
module Hledger.Web.Widget.Common
|
||||||
( accountQuery
|
( accountQuery
|
||||||
, accountOnlyQuery
|
, accountOnlyQuery
|
||||||
, balanceReportAsHtml
|
, balanceReportAsHtml
|
||||||
@ -30,7 +30,7 @@ import Yesod
|
|||||||
|
|
||||||
import Hledger
|
import Hledger
|
||||||
import Hledger.Cli.Utils (writeFileWithBackupIfChanged)
|
import Hledger.Cli.Utils (writeFileWithBackupIfChanged)
|
||||||
import Settings (manualurl)
|
import Hledger.Web.Settings (manualurl)
|
||||||
|
|
||||||
journalFile404 :: FilePath -> Journal -> HandlerFor m (FilePath, Text)
|
journalFile404 :: FilePath -> Journal -> HandlerFor m (FilePath, Text)
|
||||||
journalFile404 f j =
|
journalFile404 f j =
|
||||||
@ -2,7 +2,7 @@
|
|||||||
--
|
--
|
||||||
-- see: https://github.com/sol/hpack
|
-- see: https://github.com/sol/hpack
|
||||||
--
|
--
|
||||||
-- hash: 979ca4df732320e72b08f7b8422b1b45104ae64053d58f08ec06a62475c42981
|
-- hash: 830642fdd094b9838924e2e3865481d8bc65afb314152d5afafe2207c3d5a9a8
|
||||||
|
|
||||||
name: hledger-web
|
name: hledger-web
|
||||||
version: 1.9.99
|
version: 1.9.99
|
||||||
@ -97,6 +97,7 @@ extra-source-files:
|
|||||||
static/js/typeahead.bundle.js
|
static/js/typeahead.bundle.js
|
||||||
static/js/typeahead.bundle.min.js
|
static/js/typeahead.bundle.min.js
|
||||||
templates/add-form.hamlet
|
templates/add-form.hamlet
|
||||||
|
templates/balance-report.hamlet
|
||||||
templates/chart.hamlet
|
templates/chart.hamlet
|
||||||
templates/default-layout-wrapper.hamlet
|
templates/default-layout-wrapper.hamlet
|
||||||
templates/default-layout.hamlet
|
templates/default-layout.hamlet
|
||||||
@ -126,27 +127,28 @@ flag threaded
|
|||||||
default: True
|
default: True
|
||||||
|
|
||||||
library
|
library
|
||||||
hs-source-dirs: src
|
hs-source-dirs:
|
||||||
|
./.
|
||||||
exposed-modules:
|
exposed-modules:
|
||||||
Application
|
|
||||||
Foundation
|
|
||||||
Handler.AddR
|
|
||||||
Handler.Common
|
|
||||||
Handler.EditR
|
|
||||||
Handler.ImportR
|
|
||||||
Handler.JournalR
|
|
||||||
Handler.RegisterR
|
|
||||||
Hledger.Web
|
Hledger.Web
|
||||||
|
Hledger.Web.Application
|
||||||
|
Hledger.Web.Foundation
|
||||||
|
Hledger.Web.Handler.AddR
|
||||||
|
Hledger.Web.Handler.Common
|
||||||
|
Hledger.Web.Handler.EditR
|
||||||
|
Hledger.Web.Handler.ImportR
|
||||||
|
Hledger.Web.Handler.JournalR
|
||||||
|
Hledger.Web.Handler.RegisterR
|
||||||
|
Hledger.Web.Handler.UploadR
|
||||||
|
Hledger.Web.Import
|
||||||
Hledger.Web.Main
|
Hledger.Web.Main
|
||||||
|
Hledger.Web.Settings
|
||||||
|
Hledger.Web.Settings.Development
|
||||||
|
Hledger.Web.Settings.StaticFiles
|
||||||
Hledger.Web.WebOptions
|
Hledger.Web.WebOptions
|
||||||
Import
|
Hledger.Web.Widget.AddForm
|
||||||
Settings
|
Hledger.Web.Widget.Common
|
||||||
Settings.Development
|
|
||||||
Settings.StaticFiles
|
|
||||||
Widget.AddForm
|
|
||||||
Widget.Common
|
|
||||||
other-modules:
|
other-modules:
|
||||||
Handler.UploadR
|
|
||||||
Paths_hledger_web
|
Paths_hledger_web
|
||||||
ghc-options: -Wall -Wcompat -Wincomplete-uni-patterns -Wincomplete-record-updates -Wredundant-constraints -fwarn-tabs
|
ghc-options: -Wall -Wcompat -Wincomplete-uni-patterns -Wincomplete-record-updates -Wredundant-constraints -fwarn-tabs
|
||||||
cpp-options: -DVERSION="1.9.99"
|
cpp-options: -DVERSION="1.9.99"
|
||||||
|
|||||||
@ -44,8 +44,6 @@ extra-source-files:
|
|||||||
- hledger-web.txt
|
- hledger-web.txt
|
||||||
- hledger-web.info
|
- hledger-web.info
|
||||||
|
|
||||||
#data-files:
|
|
||||||
|
|
||||||
flags:
|
flags:
|
||||||
library-only:
|
library-only:
|
||||||
description: Build for use with "yesod devel"
|
description: Build for use with "yesod devel"
|
||||||
@ -60,7 +58,6 @@ flags:
|
|||||||
manual: false
|
manual: false
|
||||||
default: true
|
default: true
|
||||||
|
|
||||||
|
|
||||||
when:
|
when:
|
||||||
- condition: (flag(dev)) || (flag(library-only))
|
- condition: (flag(dev)) || (flag(library-only))
|
||||||
cpp-options: -DDEVELOPMENT
|
cpp-options: -DDEVELOPMENT
|
||||||
@ -76,26 +73,27 @@ ghc-options:
|
|||||||
- -fwarn-tabs
|
- -fwarn-tabs
|
||||||
|
|
||||||
library:
|
library:
|
||||||
source-dirs: src
|
source-dirs: .
|
||||||
cpp-options: -DVERSION="1.9.99"
|
cpp-options: -DVERSION="1.9.99"
|
||||||
exposed-modules:
|
exposed-modules:
|
||||||
- Application
|
|
||||||
- Foundation
|
|
||||||
- Handler.AddR
|
|
||||||
- Handler.Common
|
|
||||||
- Handler.EditR
|
|
||||||
- Handler.ImportR
|
|
||||||
- Handler.JournalR
|
|
||||||
- Handler.RegisterR
|
|
||||||
- Hledger.Web
|
- Hledger.Web
|
||||||
|
- Hledger.Web.Application
|
||||||
|
- Hledger.Web.Foundation
|
||||||
|
- Hledger.Web.Handler.AddR
|
||||||
|
- Hledger.Web.Handler.Common
|
||||||
|
- Hledger.Web.Handler.EditR
|
||||||
|
- Hledger.Web.Handler.ImportR
|
||||||
|
- Hledger.Web.Handler.JournalR
|
||||||
|
- Hledger.Web.Handler.RegisterR
|
||||||
|
- Hledger.Web.Handler.UploadR
|
||||||
|
- Hledger.Web.Import
|
||||||
- Hledger.Web.Main
|
- Hledger.Web.Main
|
||||||
|
- Hledger.Web.Settings
|
||||||
|
- Hledger.Web.Settings.Development
|
||||||
|
- Hledger.Web.Settings.StaticFiles
|
||||||
- Hledger.Web.WebOptions
|
- Hledger.Web.WebOptions
|
||||||
- Import
|
- Hledger.Web.Widget.AddForm
|
||||||
- Settings
|
- Hledger.Web.Widget.Common
|
||||||
- Settings.Development
|
|
||||||
- Settings.StaticFiles
|
|
||||||
- Widget.AddForm
|
|
||||||
- Widget.Common
|
|
||||||
dependencies:
|
dependencies:
|
||||||
- hledger-lib >=1.9.99 && <2.0
|
- hledger-lib >=1.9.99 && <2.0
|
||||||
- hledger >=1.9.99 && <2.0
|
- hledger >=1.9.99 && <2.0
|
||||||
|
|||||||
@ -1,13 +0,0 @@
|
|||||||
{-# LANGUAGE CPP #-}
|
|
||||||
module Settings.Development where
|
|
||||||
|
|
||||||
development :: Bool
|
|
||||||
development =
|
|
||||||
#if DEVELOPMENT
|
|
||||||
True
|
|
||||||
#else
|
|
||||||
False
|
|
||||||
#endif
|
|
||||||
|
|
||||||
production :: Bool
|
|
||||||
production = not development
|
|
||||||
Loading…
Reference in New Issue
Block a user