web: Clean up imports
This commit is contained in:
parent
c26674466a
commit
50e97e05fd
@ -6,42 +6,29 @@ module Application
|
|||||||
, makeFoundation
|
, makeFoundation
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.Default
|
|
||||||
import Data.IORef
|
|
||||||
import Import
|
import Import
|
||||||
import Yesod.Default.Config
|
|
||||||
import Yesod.Default.Main
|
|
||||||
import Yesod.Default.Handlers
|
|
||||||
import Network.Wai.Middleware.RequestLogger (logStdoutDev, logStdout)
|
|
||||||
import Network.HTTP.Conduit (newManager)
|
|
||||||
import Prelude (head)
|
|
||||||
|
|
||||||
-- adapt to http-conduit 1.x or 2.x when cabal macros are available, otherwise assume 2.x
|
import Data.Default (def)
|
||||||
#ifdef MIN_VERSION_http_conduit
|
import Data.IORef (newIORef, writeIORef)
|
||||||
#if MIN_VERSION_http_conduit(2,0,0)
|
import Network.Wai.Middleware.RequestLogger (logStdoutDev, logStdout)
|
||||||
#define http_conduit_2
|
|
||||||
#endif
|
|
||||||
#else
|
|
||||||
#define http_conduit_2
|
|
||||||
#endif
|
|
||||||
#ifdef http_conduit_2
|
|
||||||
import Network.HTTP.Client (defaultManagerSettings)
|
import Network.HTTP.Client (defaultManagerSettings)
|
||||||
#else
|
import Network.HTTP.Conduit (newManager)
|
||||||
import Network.HTTP.Conduit (def)
|
import Yesod.Default.Config
|
||||||
#endif
|
import Yesod.Default.Main (defaultDevelApp)
|
||||||
|
import Yesod.Default.Handlers (getFaviconR, getRobotsR)
|
||||||
|
|
||||||
-- Import all relevant handler modules here.
|
-- Import all relevant handler modules here.
|
||||||
-- Don't forget to add new modules to your cabal file!
|
-- Don't forget to add new modules to your cabal file!
|
||||||
import Handler.RootR
|
import Handler.RootR (getRootR)
|
||||||
import Handler.JournalR
|
import Handler.JournalR (getJournalR, postJournalR)
|
||||||
import Handler.RegisterR
|
import Handler.RegisterR (getRegisterR, postRegisterR)
|
||||||
import Handler.SidebarR
|
import Handler.SidebarR (getSidebarR)
|
||||||
|
|
||||||
import Hledger.Web.WebOptions (WebOpts(..), defwebopts)
|
|
||||||
import Hledger.Data (Journal, nulljournal)
|
import Hledger.Data (Journal, nulljournal)
|
||||||
import Hledger.Read (readJournalFile)
|
import Hledger.Read (readJournalFile)
|
||||||
import Hledger.Utils (error')
|
import Hledger.Utils (error')
|
||||||
import Hledger.Cli.CliOptions (defcliopts, journalFilePathFromOpts)
|
import Hledger.Cli.CliOptions (defcliopts, journalFilePathFromOpts)
|
||||||
|
import Hledger.Web.WebOptions (WebOpts(..), defwebopts)
|
||||||
|
|
||||||
-- This line actually creates our YesodDispatch instance. It is the second half
|
-- This line actually creates our YesodDispatch instance. It is the second half
|
||||||
-- of the call to mkYesodData which occurs in Foundation.hs. Please see the
|
-- of the call to mkYesodData which occurs in Foundation.hs. Please see the
|
||||||
@ -65,12 +52,7 @@ makeApplication opts j conf = do
|
|||||||
|
|
||||||
makeFoundation :: AppConfig DefaultEnv Extra -> WebOpts -> IO App
|
makeFoundation :: AppConfig DefaultEnv Extra -> WebOpts -> IO App
|
||||||
makeFoundation conf opts = do
|
makeFoundation conf opts = do
|
||||||
manager <- newManager
|
manager <- newManager defaultManagerSettings
|
||||||
#ifdef http_conduit_2
|
|
||||||
defaultManagerSettings
|
|
||||||
#else
|
|
||||||
def
|
|
||||||
#endif
|
|
||||||
s <- staticSite
|
s <- staticSite
|
||||||
jref <- newIORef nulljournal
|
jref <- newIORef nulljournal
|
||||||
return $ App conf s manager opts jref
|
return $ App conf s manager opts jref
|
||||||
|
|||||||
@ -1,53 +1,36 @@
|
|||||||
{-# LANGUAGE CPP, MultiParamTypeClasses, OverloadedStrings, RecordWildCards, QuasiQuotes, TemplateHaskell, TypeFamilies, TypeSynonymInstances, FlexibleInstances #-}
|
{-# LANGUAGE CPP, MultiParamTypeClasses, OverloadedStrings, RecordWildCards, QuasiQuotes, TemplateHaskell, TypeFamilies, TypeSynonymInstances, FlexibleInstances #-}
|
||||||
{-
|
-- | Define the web application's foundation, in the usual Yesod style.
|
||||||
|
-- See a default Yesod app's comments for more details of each part.
|
||||||
|
|
||||||
Define the web application's foundation, in the usual Yesod style.
|
|
||||||
See a default Yesod app's comments for more details of each part.
|
|
||||||
|
|
||||||
-}
|
|
||||||
module Foundation where
|
module Foundation where
|
||||||
|
|
||||||
import Prelude
|
import Data.IORef (IORef, readIORef, writeIORef)
|
||||||
import Data.IORef
|
import Data.List (isPrefixOf, sort, nub)
|
||||||
|
import Data.Maybe (fromMaybe)
|
||||||
|
import Data.Text (Text)
|
||||||
|
import qualified Data.Text as T
|
||||||
|
import Data.Time.Calendar (Day)
|
||||||
|
import Network.HTTP.Conduit (Manager)
|
||||||
|
import Text.Blaze (Markup)
|
||||||
|
import Text.Blaze.Internal (preEscapedString)
|
||||||
|
import Text.Blaze.Html.Renderer.String (renderHtml)
|
||||||
|
import Text.Hamlet (hamletFile)
|
||||||
|
import Text.JSON
|
||||||
import Yesod
|
import Yesod
|
||||||
import Yesod.Static
|
import Yesod.Static
|
||||||
import Yesod.Default.Config
|
import Yesod.Default.Config
|
||||||
#ifndef DEVELOPMENT
|
|
||||||
import Yesod.Default.Util (addStaticContentExternal)
|
|
||||||
#endif
|
|
||||||
import Network.HTTP.Conduit (Manager)
|
|
||||||
-- import qualified Settings
|
|
||||||
import Settings.StaticFiles
|
import Settings.StaticFiles
|
||||||
import Settings (staticRoot, widgetFile, Extra (..))
|
import Settings (staticRoot, widgetFile, Extra (..))
|
||||||
#ifndef DEVELOPMENT
|
#ifndef DEVELOPMENT
|
||||||
import Settings (staticDir)
|
import Settings (staticDir)
|
||||||
import Text.Jasmine (minifym)
|
import Text.Jasmine (minifym)
|
||||||
|
import Yesod.Default.Util (addStaticContentExternal)
|
||||||
#endif
|
#endif
|
||||||
import Text.Blaze.Html.Renderer.String (renderHtml)
|
|
||||||
import Text.Hamlet (hamletFile)
|
|
||||||
|
|
||||||
|
import Hledger
|
||||||
|
import Hledger.Cli
|
||||||
import Hledger.Web.WebOptions
|
import Hledger.Web.WebOptions
|
||||||
import Hledger.Data.Types
|
|
||||||
-- import Hledger.Web.Settings
|
|
||||||
-- import Hledger.Web.Settings.StaticFiles
|
|
||||||
|
|
||||||
-- for addform
|
|
||||||
import Data.List
|
|
||||||
import Data.Maybe
|
|
||||||
import Data.Text as Text (Text,pack,unpack)
|
|
||||||
import Data.Time.Calendar
|
|
||||||
#if BLAZE_HTML_0_4
|
|
||||||
import Text.Blaze (preEscapedString, Markup)
|
|
||||||
#else
|
|
||||||
import Text.Blaze (Markup)
|
|
||||||
import Text.Blaze.Internal (preEscapedString)
|
|
||||||
#endif
|
|
||||||
import Text.JSON
|
|
||||||
import Hledger.Data.Journal
|
|
||||||
import Hledger.Query
|
|
||||||
import Hledger hiding (is)
|
|
||||||
import Hledger.Cli hiding (version)
|
|
||||||
|
|
||||||
|
|
||||||
-- | 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
|
||||||
@ -62,8 +45,6 @@ data App = App
|
|||||||
, appJournal :: IORef Journal
|
, appJournal :: IORef Journal
|
||||||
}
|
}
|
||||||
|
|
||||||
-- Set up i18n messages. See the message folder.
|
|
||||||
mkMessage "App" "messages" "en"
|
|
||||||
|
|
||||||
-- This is where we define all of the routes in our application. For a full
|
-- This is where we define all of the routes in our application. For a full
|
||||||
-- explanation of the syntax, please see:
|
-- explanation of the syntax, please see:
|
||||||
@ -100,11 +81,6 @@ type Form x = Html -> MForm (HandlerT App IO) (FormResult x, Widget)
|
|||||||
instance Yesod App where
|
instance Yesod App where
|
||||||
approot = ApprootMaster $ appRoot . settings
|
approot = ApprootMaster $ appRoot . settings
|
||||||
|
|
||||||
-- -- Store session data on the client in encrypted cookies,
|
|
||||||
-- -- default session idle timeout is 120 minutes
|
|
||||||
-- makeSessionBackend _ = fmap Just $ defaultClientSessionBackend
|
|
||||||
-- (120 * 60)
|
|
||||||
-- ".hledger-web_client_session_key.aes"
|
|
||||||
-- don't use session data
|
-- don't use session data
|
||||||
makeSessionBackend _ = return Nothing
|
makeSessionBackend _ = return Nothing
|
||||||
|
|
||||||
@ -118,13 +94,6 @@ instance Yesod App where
|
|||||||
-- default-layout-wrapper is the entire page. Since the final
|
-- default-layout-wrapper is the entire page. Since the final
|
||||||
-- value passed to hamletToRepHtml cannot be a widget, this allows
|
-- value passed to hamletToRepHtml cannot be a widget, this allows
|
||||||
-- you to use normal widget features in default-layout.
|
-- you to use normal widget features in default-layout.
|
||||||
|
|
||||||
-- pc <- widgetToPageContent $ do
|
|
||||||
-- $(widgetFile "normalize")
|
|
||||||
-- addStylesheet $ StaticR css_bootstrap_css
|
|
||||||
-- $(widgetFile "default-layout")
|
|
||||||
-- hamletToRepHtml $(hamletFile "templates/default-layout-wrapper.hamlet")
|
|
||||||
|
|
||||||
pc <- widgetToPageContent $ do
|
pc <- widgetToPageContent $ do
|
||||||
addStylesheet $ StaticR css_bootstrap_min_css
|
addStylesheet $ StaticR css_bootstrap_min_css
|
||||||
addStylesheet $ StaticR css_bootstrap_datepicker_standalone_min_css
|
addStylesheet $ StaticR css_bootstrap_datepicker_standalone_min_css
|
||||||
@ -150,13 +119,6 @@ instance Yesod App where
|
|||||||
staticRootUrl <- (staticRoot . settings) <$> getYesod
|
staticRootUrl <- (staticRoot . settings) <$> getYesod
|
||||||
withUrlRenderer $(hamletFile "templates/default-layout-wrapper.hamlet")
|
withUrlRenderer $(hamletFile "templates/default-layout-wrapper.hamlet")
|
||||||
|
|
||||||
-- TODO outdated, still needed ?
|
|
||||||
-- This is done to provide an optimization for serving static files from
|
|
||||||
-- a separate domain. Please see the staticRoot setting in Settings.hs
|
|
||||||
-- urlRenderOverride y (StaticR s) =
|
|
||||||
-- Just $ uncurry (joinPath y (Settings.staticRoot $ settings y)) $ renderRoute s
|
|
||||||
urlParamRenderOverride _ _ _ = Nothing
|
|
||||||
|
|
||||||
#ifndef DEVELOPMENT
|
#ifndef DEVELOPMENT
|
||||||
-- This function creates static content files in the static folder
|
-- This function creates static content files in the static folder
|
||||||
-- and names them based on a hash of their content. This allows
|
-- and names them based on a hash of their content. This allows
|
||||||
@ -165,9 +127,6 @@ instance Yesod App where
|
|||||||
addStaticContent = addStaticContentExternal minifym base64md5 Settings.staticDir (StaticR . flip StaticRoute [])
|
addStaticContent = addStaticContentExternal minifym base64md5 Settings.staticDir (StaticR . flip StaticRoute [])
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
-- Place Javascript at bottom of the body tag so the rest of the page loads first
|
|
||||||
jsLoader _ = BottomOfBody
|
|
||||||
|
|
||||||
-- This instance is required to use forms. You can modify renderMessage to
|
-- This instance is required to use forms. You can modify renderMessage to
|
||||||
-- achieve customized and internationalized form validation messages.
|
-- achieve customized and internationalized form validation messages.
|
||||||
instance RenderMessage App FormMessage where
|
instance RenderMessage App FormMessage where
|
||||||
@ -177,13 +136,6 @@ instance RenderMessage App FormMessage where
|
|||||||
getExtra :: Handler Extra
|
getExtra :: Handler Extra
|
||||||
getExtra = fmap (appExtra . settings) getYesod
|
getExtra = fmap (appExtra . settings) getYesod
|
||||||
|
|
||||||
-- Note: previous versions of the scaffolding included a deliver function to
|
|
||||||
-- send emails. Unfortunately, there are too many different options for us to
|
|
||||||
-- give a reasonable default. Instead, the information is available on the
|
|
||||||
-- wiki:
|
|
||||||
--
|
|
||||||
-- https://github.com/yesodweb/yesod/wiki/Sending-email
|
|
||||||
|
|
||||||
|
|
||||||
----------------------------------------------------------------------
|
----------------------------------------------------------------------
|
||||||
-- template and handler utilities
|
-- template and handler utilities
|
||||||
@ -215,8 +167,8 @@ nullviewdata = viewdataWithDateAndParams nulldate "" "" ""
|
|||||||
-- | Make a ViewData using the given date and request parameters, and defaults elsewhere.
|
-- | Make a ViewData using the given date and request parameters, and defaults elsewhere.
|
||||||
viewdataWithDateAndParams :: Day -> String -> String -> String -> ViewData
|
viewdataWithDateAndParams :: Day -> String -> String -> String -> ViewData
|
||||||
viewdataWithDateAndParams d q a p =
|
viewdataWithDateAndParams d q a p =
|
||||||
let (querymatcher,queryopts) = parseQuery d (pack q)
|
let (querymatcher,queryopts) = parseQuery d (T.pack q)
|
||||||
(acctsmatcher,acctsopts) = parseQuery d (pack a)
|
(acctsmatcher,acctsopts) = parseQuery d (T.pack a)
|
||||||
in VD {
|
in VD {
|
||||||
opts = defwebopts
|
opts = defwebopts
|
||||||
,j = nulljournal
|
,j = nulljournal
|
||||||
@ -284,7 +236,7 @@ getViewData = do
|
|||||||
|
|
||||||
-- | Get the named request parameter, or the empty string if not present.
|
-- | Get the named request parameter, or the empty string if not present.
|
||||||
getParameterOrNull :: String -> Handler String
|
getParameterOrNull :: String -> Handler String
|
||||||
getParameterOrNull p = unpack `fmap` fromMaybe "" <$> lookupGetParam (pack p)
|
getParameterOrNull p = T.unpack `fmap` fromMaybe "" <$> lookupGetParam (T.pack p)
|
||||||
|
|
||||||
-- | Get the message that was set by the last request, in a
|
-- | Get the message that was set by the last request, in a
|
||||||
-- referentially transparent manner (allowing multiple reads).
|
-- referentially transparent manner (allowing multiple reads).
|
||||||
@ -391,4 +343,3 @@ journalradio journalfilepaths = [hamlet|
|
|||||||
<span class="input-lg" style="position:relative; top:-8px; left:8px;">#{p}
|
<span class="input-lg" style="position:relative; top:-8px; left:8px;">#{p}
|
||||||
<input name=journal type=radio value=#{p} class="form-control" style="width:auto; display:inline;">
|
<input name=journal type=radio value=#{p} class="form-control" style="width:auto; display:inline;">
|
||||||
|]
|
|]
|
||||||
|
|
||||||
|
|||||||
@ -8,22 +8,18 @@ module Handler.AddForm where
|
|||||||
import Import
|
import Import
|
||||||
|
|
||||||
import Control.Monad.State.Strict (evalStateT)
|
import Control.Monad.State.Strict (evalStateT)
|
||||||
import Data.Either (lefts,rights)
|
|
||||||
import Data.List (sort)
|
import Data.List (sort)
|
||||||
|
import Data.Either (lefts, rights)
|
||||||
import qualified Data.List as L (head) -- qualified keeps dev & prod builds warning-free
|
import qualified Data.List as L (head) -- qualified keeps dev & prod builds warning-free
|
||||||
import Data.Text (append, pack, unpack)
|
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import Data.Time.Calendar
|
import Data.Time.Calendar
|
||||||
import Data.Void (Void)
|
import Data.Void (Void)
|
||||||
import Text.Megaparsec
|
import Text.Megaparsec
|
||||||
import Text.Megaparsec.Char
|
import Text.Megaparsec.Char
|
||||||
|
|
||||||
import Hledger.Utils
|
import Hledger
|
||||||
import Hledger.Data
|
|
||||||
import Hledger.Read
|
|
||||||
import Hledger.Cli.Commands.Add (appendToJournalFileOrStdout)
|
import Hledger.Cli.Commands.Add (appendToJournalFileOrStdout)
|
||||||
|
|
||||||
|
|
||||||
-- Part of the data required from the add form.
|
-- Part of the data required from the add form.
|
||||||
-- Don't know how to handle the variable posting fields with yesod-form yet.
|
-- Don't know how to handle the variable posting fields with yesod-form yet.
|
||||||
data AddForm = AddForm
|
data AddForm = AddForm
|
||||||
@ -49,17 +45,17 @@ postAddForm = do
|
|||||||
let
|
let
|
||||||
validateJournalFile :: Text -> Either FormMessage Text
|
validateJournalFile :: Text -> Either FormMessage Text
|
||||||
validateJournalFile f
|
validateJournalFile f
|
||||||
| unpack f `elem` journalFilePaths j = Right f
|
| T.unpack f `elem` journalFilePaths j = Right f
|
||||||
| otherwise = Left $ MsgInvalidEntry $ pack "the selected journal file \"" `append` f `append` "\"is unknown"
|
| otherwise = Left $ MsgInvalidEntry $ T.pack "the selected journal file \"" <> f <> "\"is unknown"
|
||||||
|
|
||||||
validateDate :: Text -> Handler (Either FormMessage Day)
|
validateDate :: Text -> Handler (Either FormMessage Day)
|
||||||
validateDate s = return $
|
validateDate s = return $
|
||||||
case fixSmartDateStrEither' today $ T.pack $ strip $ unpack s of
|
case fixSmartDateStrEither' today $ T.pack $ strip $ T.unpack s of
|
||||||
Right d -> Right d
|
Right d -> Right d
|
||||||
Left _ -> Left $ MsgInvalidEntry $ pack "could not parse date \"" `append` s `append` pack "\":" -- ++ show e)
|
Left _ -> Left $ MsgInvalidEntry $ "could not parse date \"" <> s <> "\":"
|
||||||
|
|
||||||
formresult <- runInputPostResult $ AddForm
|
formresult <- runInputPostResult $ AddForm
|
||||||
<$> ireq (checkMMap validateDate (pack . show) textField) "date"
|
<$> ireq (checkMMap validateDate (T.pack . show) textField) "date"
|
||||||
<*> iopt textField "description"
|
<*> iopt textField "description"
|
||||||
<*> iopt (check validateJournalFile textField) "journal"
|
<*> iopt (check validateJournalFile textField) "journal"
|
||||||
|
|
||||||
@ -72,8 +68,8 @@ postAddForm = do
|
|||||||
,addFormDescription=mdesc
|
,addFormDescription=mdesc
|
||||||
,addFormJournalFile=mjournalfile
|
,addFormJournalFile=mjournalfile
|
||||||
} = dat
|
} = dat
|
||||||
desc = maybe "" unpack mdesc
|
desc = maybe "" T.unpack mdesc
|
||||||
journalfile = maybe (journalFilePath j) unpack mjournalfile
|
journalfile = maybe (journalFilePath j) T.unpack mjournalfile
|
||||||
|
|
||||||
-- 2. the fixed fields look good; now process the posting fields adhocly,
|
-- 2. the fixed fields look good; now process the posting fields adhocly,
|
||||||
-- getting either errors or a balanced transaction
|
-- getting either errors or a balanced transaction
|
||||||
|
|||||||
@ -6,22 +6,17 @@ module Handler.Common where
|
|||||||
|
|
||||||
import Import
|
import Import
|
||||||
|
|
||||||
-- import Data.Text (Text)
|
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import Data.Time.Calendar
|
import Data.Time.Calendar (Day, toGregorian)
|
||||||
import System.FilePath (takeFileName)
|
import System.FilePath (takeFileName)
|
||||||
#if BLAZE_HTML_0_4
|
|
||||||
import Text.Blaze (preEscapedString)
|
|
||||||
#else
|
|
||||||
import Text.Blaze.Internal (preEscapedString)
|
import Text.Blaze.Internal (preEscapedString)
|
||||||
#endif
|
import Text.Printf (printf)
|
||||||
import Text.Printf
|
|
||||||
|
|
||||||
import Hledger.Utils
|
import Hledger.Cli.CliOptions
|
||||||
import Hledger.Data
|
import Hledger.Data
|
||||||
import Hledger.Query
|
import Hledger.Query
|
||||||
import Hledger.Reports
|
import Hledger.Reports
|
||||||
import Hledger.Cli.CliOptions
|
import Hledger.Utils
|
||||||
import Hledger.Web.WebOptions
|
import Hledger.Web.WebOptions
|
||||||
|
|
||||||
-------------------------------------------------------------------------------
|
-------------------------------------------------------------------------------
|
||||||
|
|||||||
@ -3,18 +3,18 @@
|
|||||||
|
|
||||||
module Handler.JournalR where
|
module Handler.JournalR where
|
||||||
|
|
||||||
-- import Data.Text (Text)
|
|
||||||
import qualified Data.Text as T
|
|
||||||
import Import
|
import Import
|
||||||
|
|
||||||
|
import qualified Data.Text as T
|
||||||
|
|
||||||
import Handler.AddForm
|
import Handler.AddForm
|
||||||
import Handler.Common
|
import Handler.Common
|
||||||
|
|
||||||
|
import Hledger.Cli.CliOptions
|
||||||
import Hledger.Data
|
import Hledger.Data
|
||||||
import Hledger.Query
|
import Hledger.Query
|
||||||
import Hledger.Reports
|
import Hledger.Reports
|
||||||
import Hledger.Utils
|
import Hledger.Utils
|
||||||
import Hledger.Cli.CliOptions
|
|
||||||
import Hledger.Web.WebOptions
|
import Hledger.Web.WebOptions
|
||||||
|
|
||||||
-- | The formatted journal view, with sidebar.
|
-- | The formatted journal view, with sidebar.
|
||||||
|
|||||||
@ -5,11 +5,10 @@ module Handler.RegisterR where
|
|||||||
|
|
||||||
import Import
|
import Import
|
||||||
|
|
||||||
import Data.List
|
import Data.List (intersperse)
|
||||||
import Data.Maybe
|
import Data.Maybe (fromMaybe, isJust)
|
||||||
-- import Data.Text (Text)
|
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import Safe
|
import Safe (headMay)
|
||||||
|
|
||||||
import Handler.AddForm
|
import Handler.AddForm
|
||||||
import Handler.Common
|
import Handler.Common
|
||||||
|
|||||||
@ -4,13 +4,9 @@
|
|||||||
|
|
||||||
module Handler.Utils where
|
module Handler.Utils where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
import Data.Time.Calendar
|
import Data.Time.Calendar
|
||||||
import Data.Time.Clock
|
import Data.Time.Clock
|
||||||
import Data.Time.Format
|
import Data.Time.Format
|
||||||
#if !(MIN_VERSION_time(1,5,0))
|
|
||||||
import System.Locale (defaultTimeLocale)
|
|
||||||
#endif
|
|
||||||
|
|
||||||
numbered :: [a] -> [(Int,a)]
|
numbered :: [a] -> [(Int,a)]
|
||||||
numbered = zip [1..]
|
numbered = zip [1..]
|
||||||
|
|||||||
@ -2,12 +2,12 @@
|
|||||||
Re-export the modules of the hledger-web program.
|
Re-export the modules of the hledger-web program.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Hledger.Web (
|
module Hledger.Web
|
||||||
module Hledger.Web.WebOptions,
|
( module Hledger.Web.WebOptions
|
||||||
module Hledger.Web.Main,
|
, module Hledger.Web.Main
|
||||||
tests_Hledger_Web
|
, tests_Hledger_Web
|
||||||
)
|
) where
|
||||||
where
|
|
||||||
import Test.HUnit
|
import Test.HUnit
|
||||||
|
|
||||||
import Hledger.Web.WebOptions
|
import Hledger.Web.WebOptions
|
||||||
|
|||||||
@ -7,28 +7,26 @@ Released under GPL version 3 or later.
|
|||||||
|
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Hledger.Web.Main
|
module Hledger.Web.Main where
|
||||||
where
|
|
||||||
|
|
||||||
-- yesod scaffold imports
|
import Control.Monad ((<=<), when)
|
||||||
import Yesod.Default.Config --(fromArgs)
|
import Data.Default (def)
|
||||||
-- import Yesod.Default.Main (defaultMain)
|
import Data.String (fromString)
|
||||||
import Settings -- (parseExtra)
|
import qualified Data.Text as T
|
||||||
import Application (makeApplication)
|
|
||||||
import Data.String
|
|
||||||
import Network.Wai.Handler.Warp (runSettings, defaultSettings, setHost, setPort)
|
import Network.Wai.Handler.Warp (runSettings, defaultSettings, setHost, setPort)
|
||||||
import Network.Wai.Handler.Launch (runHostPortUrl)
|
import Network.Wai.Handler.Launch (runHostPortUrl)
|
||||||
--
|
import Prelude hiding (putStrLn)
|
||||||
import Control.Monad
|
|
||||||
import Data.Text (pack)
|
|
||||||
import System.Exit (exitSuccess)
|
import System.Exit (exitSuccess)
|
||||||
import System.IO (hFlush, stdout)
|
import System.IO (hFlush, stdout)
|
||||||
import Text.Printf
|
import Text.Printf (printf)
|
||||||
import Prelude hiding (putStrLn)
|
import Yesod.Default.Config (AppConfig(..), DefaultEnv(Development))
|
||||||
|
|
||||||
|
import Application (makeApplication)
|
||||||
|
import Settings (Extra(..))
|
||||||
|
|
||||||
import Hledger
|
import Hledger
|
||||||
import Hledger.Utils.UTF8IOCompat (putStrLn)
|
|
||||||
import Hledger.Cli hiding (progname,prognameandversion)
|
import Hledger.Cli hiding (progname,prognameandversion)
|
||||||
|
import Hledger.Utils.UTF8IOCompat (putStrLn)
|
||||||
import Hledger.Web.WebOptions
|
import Hledger.Web.WebOptions
|
||||||
|
|
||||||
|
|
||||||
@ -74,11 +72,11 @@ web opts j = do
|
|||||||
h = host_ opts
|
h = host_ opts
|
||||||
p = port_ opts
|
p = port_ opts
|
||||||
u = base_url_ opts
|
u = base_url_ opts
|
||||||
staticRoot = pack <$> file_url_ opts
|
staticRoot = T.pack <$> file_url_ opts
|
||||||
appconfig = AppConfig{appEnv = Development
|
appconfig = AppConfig{appEnv = Development
|
||||||
,appHost = fromString h
|
,appHost = fromString h
|
||||||
,appPort = p
|
,appPort = p
|
||||||
,appRoot = pack u
|
,appRoot = T.pack u
|
||||||
,appExtra = Extra "" Nothing staticRoot
|
,appExtra = Extra "" Nothing staticRoot
|
||||||
}
|
}
|
||||||
app <- makeApplication opts j' appconfig
|
app <- makeApplication opts j' appconfig
|
||||||
|
|||||||
@ -1,13 +1,13 @@
|
|||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
module Hledger.Web.WebOptions
|
module Hledger.Web.WebOptions where
|
||||||
where
|
|
||||||
import Prelude
|
|
||||||
import Data.Default
|
|
||||||
import Data.Maybe
|
|
||||||
import System.Environment
|
|
||||||
|
|
||||||
import Hledger.Cli hiding (progname,version,prognameandversion)
|
import Data.Default (def)
|
||||||
import Settings
|
import Data.Maybe (fromMaybe)
|
||||||
|
import System.Environment (getArgs)
|
||||||
|
|
||||||
|
import Settings (defhost, defport, defbaseurl)
|
||||||
|
|
||||||
|
import Hledger.Cli hiding (progname, version)
|
||||||
|
|
||||||
progname, version :: String
|
progname, version :: String
|
||||||
progname = "hledger-web"
|
progname = "hledger-web"
|
||||||
|
|||||||
@ -6,16 +6,16 @@
|
|||||||
-- declared in the Foundation.hs file.
|
-- declared in the Foundation.hs file.
|
||||||
module Settings where
|
module Settings where
|
||||||
|
|
||||||
import Prelude
|
import Data.Default (def)
|
||||||
import Text.Shakespeare.Text (st)
|
|
||||||
import Language.Haskell.TH.Syntax
|
|
||||||
import Yesod.Default.Config
|
|
||||||
import Yesod.Default.Util
|
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import Data.Yaml
|
import Data.Yaml
|
||||||
import Settings.Development
|
import Language.Haskell.TH.Syntax (Q, Exp)
|
||||||
import Data.Default (def)
|
|
||||||
import Text.Hamlet
|
import Text.Hamlet
|
||||||
|
import Text.Shakespeare.Text (st)
|
||||||
|
import Yesod.Default.Config
|
||||||
|
import Yesod.Default.Util
|
||||||
|
|
||||||
|
import Settings.Development
|
||||||
|
|
||||||
|
|
||||||
hledgerorgurl, manualurl :: String
|
hledgerorgurl, manualurl :: String
|
||||||
|
|||||||
@ -1,8 +1,6 @@
|
|||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
module Settings.Development where
|
module Settings.Development where
|
||||||
|
|
||||||
import Prelude
|
|
||||||
|
|
||||||
development :: Bool
|
development :: Bool
|
||||||
development =
|
development =
|
||||||
#if DEVELOPMENT
|
#if DEVELOPMENT
|
||||||
|
|||||||
@ -1,12 +1,11 @@
|
|||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
module Settings.StaticFiles where
|
module Settings.StaticFiles where
|
||||||
|
|
||||||
import Prelude (IO, putStrLn, (++), (>>), return)
|
|
||||||
import System.IO (stdout, hFlush)
|
import System.IO (stdout, hFlush)
|
||||||
import Yesod.Static
|
import Yesod.Static (Static, embed, publicFiles, staticDevel)
|
||||||
import qualified Yesod.Static as Static
|
|
||||||
import Settings (staticDir)
|
import Settings (staticDir)
|
||||||
import Settings.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
|
||||||
@ -20,14 +19,14 @@ import Settings.Development
|
|||||||
-- $(staticFiles Settings.staticDir)
|
-- $(staticFiles Settings.staticDir)
|
||||||
|
|
||||||
|
|
||||||
staticSite :: IO Static.Static
|
staticSite :: IO Static
|
||||||
staticSite =
|
staticSite =
|
||||||
if development
|
if development
|
||||||
then (do
|
then (do
|
||||||
putStrLn ("Using web files from: " ++ staticDir ++ "/") >> hFlush stdout
|
putStrLn ("Using web files from: " ++ staticDir ++ "/") >> hFlush stdout
|
||||||
Static.staticDevel staticDir)
|
staticDevel staticDir)
|
||||||
else (do
|
else (do
|
||||||
-- putStrLn "Using built-in web files" >> hFlush stdout
|
-- putStrLn "Using built-in web files" >> hFlush stdout
|
||||||
return $(Static.embed staticDir))
|
return $(embed staticDir))
|
||||||
|
|
||||||
$(publicFiles staticDir)
|
$(publicFiles staticDir)
|
||||||
|
|||||||
@ -38,7 +38,6 @@ extra-source-files:
|
|||||||
hledger-web.1
|
hledger-web.1
|
||||||
hledger-web.info
|
hledger-web.info
|
||||||
hledger-web.txt
|
hledger-web.txt
|
||||||
messages/en.msg
|
|
||||||
README
|
README
|
||||||
static/css/bootstrap-datepicker.standalone.min.css
|
static/css/bootstrap-datepicker.standalone.min.css
|
||||||
static/css/bootstrap-theme.css
|
static/css/bootstrap-theme.css
|
||||||
@ -139,7 +138,7 @@ library
|
|||||||
Settings.StaticFiles
|
Settings.StaticFiles
|
||||||
other-modules:
|
other-modules:
|
||||||
Paths_hledger_web
|
Paths_hledger_web
|
||||||
ghc-options: -Wall -fno-warn-unused-do-bind -fno-warn-name-shadowing -fno-warn-missing-signatures -fno-warn-type-defaults -fno-warn-orphans
|
ghc-options: -Wall
|
||||||
cpp-options: -DVERSION="1.9.99"
|
cpp-options: -DVERSION="1.9.99"
|
||||||
build-depends:
|
build-depends:
|
||||||
HUnit
|
HUnit
|
||||||
|
|||||||
@ -1 +0,0 @@
|
|||||||
Hello: Hello
|
|
||||||
@ -30,7 +30,6 @@ extra-source-files:
|
|||||||
- config/robots.txt
|
- config/robots.txt
|
||||||
- config/routes
|
- config/routes
|
||||||
- config/settings.yml
|
- config/settings.yml
|
||||||
- messages/*.msg
|
|
||||||
- static/css/*.css
|
- static/css/*.css
|
||||||
- static/css/*.map
|
- static/css/*.map
|
||||||
- static/fonts/*.eot
|
- static/fonts/*.eot
|
||||||
@ -107,11 +106,11 @@ when:
|
|||||||
|
|
||||||
ghc-options:
|
ghc-options:
|
||||||
- -Wall
|
- -Wall
|
||||||
- -fno-warn-unused-do-bind
|
- -Wcompat
|
||||||
- -fno-warn-name-shadowing
|
- -Wincomplete-uni-patterns
|
||||||
- -fno-warn-missing-signatures
|
- -Wincomplete-record-updates
|
||||||
- -fno-warn-type-defaults
|
- -Wredundant-constraints
|
||||||
- -fno-warn-orphans
|
- -fwarn-tabs
|
||||||
|
|
||||||
library:
|
library:
|
||||||
cpp-options: -DVERSION="1.9.99"
|
cpp-options: -DVERSION="1.9.99"
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user