web: make the add form a modal dialog
The add form has become a modal dialog, and been moved into the default template. This simplifies some things, for now. Eg it's easily accessible from any page.
This commit is contained in:
parent
ed3fd58fb9
commit
009df13baf
@ -8,6 +8,7 @@ See a default Yesod app's comments for more details of each part.
|
|||||||
module Foundation where
|
module Foundation where
|
||||||
|
|
||||||
import Prelude
|
import Prelude
|
||||||
|
import Control.Applicative ((<$>))
|
||||||
import Data.IORef
|
import Data.IORef
|
||||||
import Yesod
|
import Yesod
|
||||||
import Yesod.Static
|
import Yesod.Static
|
||||||
@ -31,6 +32,23 @@ import Hledger.Data.Types
|
|||||||
-- import Hledger.Web.Settings
|
-- import Hledger.Web.Settings
|
||||||
-- import Hledger.Web.Settings.StaticFiles
|
-- 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
|
||||||
|
import System.FilePath (takeFileName)
|
||||||
|
#if BLAZE_HTML_0_4
|
||||||
|
import Text.Blaze (preEscapedString)
|
||||||
|
#else
|
||||||
|
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
|
||||||
@ -120,6 +138,8 @@ instance Yesod App where
|
|||||||
addScript $ StaticR hledger_js
|
addScript $ StaticR hledger_js
|
||||||
$(widgetFile "default-layout")
|
$(widgetFile "default-layout")
|
||||||
|
|
||||||
|
staticRootUrl <- (staticRoot . settings) <$> getYesod
|
||||||
|
vd@VD{..} <- getViewData
|
||||||
giveUrlRenderer $(hamletFile "templates/default-layout-wrapper.hamlet")
|
giveUrlRenderer $(hamletFile "templates/default-layout-wrapper.hamlet")
|
||||||
|
|
||||||
-- This is done to provide an optimization for serving static files from
|
-- This is done to provide an optimization for serving static files from
|
||||||
@ -159,3 +179,224 @@ getExtra = fmap (appExtra . settings) getYesod
|
|||||||
-- wiki:
|
-- wiki:
|
||||||
--
|
--
|
||||||
-- https://github.com/yesodweb/yesod/wiki/Sending-email
|
-- https://github.com/yesodweb/yesod/wiki/Sending-email
|
||||||
|
|
||||||
|
|
||||||
|
----------------------------------------------------------------------
|
||||||
|
-- template and handler utilities
|
||||||
|
|
||||||
|
-- view data, used by the add form and handlers
|
||||||
|
|
||||||
|
-- | A bundle of data useful for hledger-web request handlers and templates.
|
||||||
|
data ViewData = VD {
|
||||||
|
opts :: WebOpts -- ^ the command-line options at startup
|
||||||
|
,here :: AppRoute -- ^ the current route
|
||||||
|
,msg :: Maybe Html -- ^ the current UI message if any, possibly from the current request
|
||||||
|
,today :: Day -- ^ today's date (for queries containing relative dates)
|
||||||
|
,j :: Journal -- ^ the up-to-date parsed unfiltered journal
|
||||||
|
,q :: String -- ^ the current q parameter, the main query expression
|
||||||
|
,m :: Query -- ^ a query parsed from the q parameter
|
||||||
|
,qopts :: [QueryOpt] -- ^ query options parsed from the q parameter
|
||||||
|
,am :: Query -- ^ a query parsed from the accounts sidebar query expr ("a" parameter)
|
||||||
|
,aopts :: [QueryOpt] -- ^ query options parsed from the accounts sidebar query expr
|
||||||
|
,showpostings :: Bool -- ^ current p parameter, 1 or 0 shows/hides all postings where applicable
|
||||||
|
,showsidebar :: Bool -- ^ current showsidebar cookie value
|
||||||
|
}
|
||||||
|
|
||||||
|
-- | Make a default ViewData, using day 0 as today's date.
|
||||||
|
nullviewdata :: ViewData
|
||||||
|
nullviewdata = viewdataWithDateAndParams nulldate "" "" ""
|
||||||
|
|
||||||
|
-- | Make a ViewData using the given date and request parameters, and defaults elsewhere.
|
||||||
|
viewdataWithDateAndParams :: Day -> String -> String -> String -> ViewData
|
||||||
|
viewdataWithDateAndParams d q a p =
|
||||||
|
let (querymatcher,queryopts) = parseQuery d q
|
||||||
|
(acctsmatcher,acctsopts) = parseQuery d a
|
||||||
|
in VD {
|
||||||
|
opts = defwebopts
|
||||||
|
,j = nulljournal
|
||||||
|
,here = RootR
|
||||||
|
,msg = Nothing
|
||||||
|
,today = d
|
||||||
|
,q = q
|
||||||
|
,m = querymatcher
|
||||||
|
,qopts = queryopts
|
||||||
|
,am = acctsmatcher
|
||||||
|
,aopts = acctsopts
|
||||||
|
,showpostings = p == "1"
|
||||||
|
,showsidebar = False
|
||||||
|
}
|
||||||
|
|
||||||
|
-- | Gather data used by handlers and templates in the current request.
|
||||||
|
getViewData :: Handler ViewData
|
||||||
|
getViewData = do
|
||||||
|
app <- getYesod
|
||||||
|
let opts@WebOpts{cliopts_=copts@CliOpts{reportopts_=ropts}} = appOpts app
|
||||||
|
(j, err) <- getCurrentJournal app copts{reportopts_=ropts{no_elide_=True}}
|
||||||
|
msg <- getMessageOr err
|
||||||
|
Just here <- getCurrentRoute
|
||||||
|
today <- liftIO getCurrentDay
|
||||||
|
q <- getParameterOrNull "q"
|
||||||
|
a <- getParameterOrNull "a"
|
||||||
|
p <- getParameterOrNull "p"
|
||||||
|
cookies <- reqCookies <$> getRequest
|
||||||
|
let showsidebar = maybe False (=="1") $ lookup "showsidebar" cookies
|
||||||
|
return (viewdataWithDateAndParams today q a p){
|
||||||
|
opts=opts
|
||||||
|
,msg=msg
|
||||||
|
,here=here
|
||||||
|
,today=today
|
||||||
|
,j=j
|
||||||
|
,showsidebar=showsidebar
|
||||||
|
}
|
||||||
|
where
|
||||||
|
-- | Update our copy of the journal if the file changed. If there is an
|
||||||
|
-- error while reloading, keep the old one and return the error, and set a
|
||||||
|
-- ui message.
|
||||||
|
getCurrentJournal :: App -> CliOpts -> Handler (Journal, Maybe String)
|
||||||
|
getCurrentJournal app opts = do
|
||||||
|
-- XXX put this inside atomicModifyIORef' for thread safety
|
||||||
|
j <- liftIO $ readIORef $ appJournal app
|
||||||
|
(jE, changed) <- liftIO $ journalReloadIfChanged opts j
|
||||||
|
if not changed
|
||||||
|
then return (j,Nothing)
|
||||||
|
else case jE of
|
||||||
|
Right j' -> do liftIO $ writeIORef (appJournal app) j'
|
||||||
|
return (j',Nothing)
|
||||||
|
Left e -> do setMessage $ "error while reading" {- ++ ": " ++ e-}
|
||||||
|
return (j, Just e)
|
||||||
|
|
||||||
|
-- | Get the named request parameter, or the empty string if not present.
|
||||||
|
getParameterOrNull :: String -> Handler String
|
||||||
|
getParameterOrNull p = unpack `fmap` fromMaybe "" <$> lookupGetParam (pack p)
|
||||||
|
|
||||||
|
-- | Get the message set by the last request, or the newer message provided, if any.
|
||||||
|
getMessageOr :: Maybe String -> Handler (Maybe Html)
|
||||||
|
getMessageOr mnewmsg = do
|
||||||
|
oldmsg <- getMessage
|
||||||
|
return $ maybe oldmsg (Just . toHtml) mnewmsg
|
||||||
|
|
||||||
|
-- add form dialog, part of the default template
|
||||||
|
|
||||||
|
-- | Add transaction form.
|
||||||
|
addform :: Text -> ViewData -> HtmlUrl AppRoute
|
||||||
|
addform _ vd@VD{..} = [hamlet|
|
||||||
|
<script language="javascript">
|
||||||
|
jQuery(document).ready(function() {
|
||||||
|
|
||||||
|
/* set up type-ahead fields */
|
||||||
|
|
||||||
|
datesSuggester = new Bloodhound({
|
||||||
|
local:#{listToJsonValueObjArrayStr dates},
|
||||||
|
limit:100,
|
||||||
|
datumTokenizer: function(d) { return [d.value]; },
|
||||||
|
queryTokenizer: function(q) { return [q]; }
|
||||||
|
});
|
||||||
|
datesSuggester.initialize();
|
||||||
|
jQuery('#date').typeahead(
|
||||||
|
{
|
||||||
|
highlight: true
|
||||||
|
},
|
||||||
|
{
|
||||||
|
source: datesSuggester.ttAdapter()
|
||||||
|
}
|
||||||
|
);
|
||||||
|
|
||||||
|
accountsSuggester = new Bloodhound({
|
||||||
|
local:#{listToJsonValueObjArrayStr accts},
|
||||||
|
limit:100,
|
||||||
|
datumTokenizer: function(d) { return [d.value]; },
|
||||||
|
queryTokenizer: function(q) { return [q]; }
|
||||||
|
/*
|
||||||
|
datumTokenizer: Bloodhound.tokenizers.obj.whitespace('value'),
|
||||||
|
datumTokenizer: Bloodhound.tokenizers.whitespace(d.value)
|
||||||
|
queryTokenizer: Bloodhound.tokenizers.whitespace
|
||||||
|
*/
|
||||||
|
});
|
||||||
|
accountsSuggester.initialize();
|
||||||
|
jQuery('#account1,#account2').typeahead(
|
||||||
|
{
|
||||||
|
/* minLength: 3, */
|
||||||
|
highlight: true
|
||||||
|
},
|
||||||
|
{
|
||||||
|
source: accountsSuggester.ttAdapter()
|
||||||
|
}
|
||||||
|
);
|
||||||
|
|
||||||
|
descriptionsSuggester = new Bloodhound({
|
||||||
|
local:#{listToJsonValueObjArrayStr descriptions},
|
||||||
|
limit:100,
|
||||||
|
datumTokenizer: function(d) { return [d.value]; },
|
||||||
|
queryTokenizer: function(q) { return [q]; }
|
||||||
|
});
|
||||||
|
descriptionsSuggester.initialize();
|
||||||
|
jQuery('#description').typeahead(
|
||||||
|
{
|
||||||
|
highlight: true
|
||||||
|
},
|
||||||
|
{
|
||||||
|
source: descriptionsSuggester.ttAdapter()
|
||||||
|
}
|
||||||
|
);
|
||||||
|
|
||||||
|
});
|
||||||
|
|
||||||
|
<form#addform method=POST style="position:relative;">
|
||||||
|
<table.form style="width:100%; white-space:nowrap;">
|
||||||
|
<tr>
|
||||||
|
<td colspan=4>
|
||||||
|
<table style="width:100%;">
|
||||||
|
<tr#descriptionrow>
|
||||||
|
<td>
|
||||||
|
<input #date .form-control .input-lg type=text size=15 name=date placeholder="Date" value=#{date}>
|
||||||
|
<td>
|
||||||
|
<input #description .form-control .input-lg type=text size=40 name=description placeholder="Description">
|
||||||
|
$forall n <- postingnums
|
||||||
|
^{postingfields vd n}
|
||||||
|
|]
|
||||||
|
where
|
||||||
|
date = "today" :: String
|
||||||
|
dates = ["today","yesterday","tomorrow"] :: [String]
|
||||||
|
descriptions = sort $ nub $ map tdescription $ jtxns j
|
||||||
|
accts = sort $ journalAccountNamesUsed j
|
||||||
|
listToJsonValueObjArrayStr as = preEscapedString $ encode $ JSArray $ map (\a -> JSObject $ toJSObject [("value", showJSON a)]) as
|
||||||
|
numpostings = 2
|
||||||
|
postingnums = [1..numpostings]
|
||||||
|
postingfields :: ViewData -> Int -> HtmlUrl AppRoute
|
||||||
|
postingfields _ n = [hamlet|
|
||||||
|
<tr .posting .#{lastclass}>
|
||||||
|
<td style="padding-left:2em;">
|
||||||
|
<input ##{acctvar} .form-control .input-lg style="width:100%;" type=text name=#{acctvar} placeholder="#{acctph}">
|
||||||
|
^{amtfieldorsubmitbtn}
|
||||||
|
|]
|
||||||
|
where
|
||||||
|
islast = n == numpostings
|
||||||
|
lastclass = if islast then "lastrow" else "" :: String
|
||||||
|
acctvar = "account" ++ show n
|
||||||
|
acctph = "Account " ++ show n
|
||||||
|
amtfieldorsubmitbtn
|
||||||
|
| not islast = [hamlet|
|
||||||
|
<td>
|
||||||
|
<input ##{amtvar} .form-control .input-lg type=text size=10 name=#{amtvar} placeholder="#{amtph}">
|
||||||
|
|]
|
||||||
|
| otherwise = [hamlet|
|
||||||
|
<td #addbtncell style="text-align:right;">
|
||||||
|
<input type=hidden name=action value=add>
|
||||||
|
<button type=submit .btn .btn-lg name=submit>add
|
||||||
|
$if length files' > 1
|
||||||
|
<br>to: ^{journalselect files'}
|
||||||
|
|]
|
||||||
|
where
|
||||||
|
amtvar = "amount" ++ show n
|
||||||
|
amtph = "Amount " ++ show n
|
||||||
|
files' = [(takeFileName f,s) | (f,s) <- files j]
|
||||||
|
|
||||||
|
-- <button .btn style="font-size:18px;" type=submit title="Add this transaction">Add
|
||||||
|
|
||||||
|
journalselect :: [(FilePath,String)] -> HtmlUrl AppRoute
|
||||||
|
journalselect journalfiles = [hamlet|
|
||||||
|
<select id=journalselect name=journal onchange="editformJournalSelect(event)">
|
||||||
|
$forall f <- journalfiles
|
||||||
|
<option value=#{fst f}>#{fst f}
|
||||||
|
|]
|
||||||
|
|
||||||
|
|||||||
@ -15,7 +15,6 @@ import Text.Blaze (preEscapedString)
|
|||||||
import Text.Blaze.Internal (preEscapedString)
|
import Text.Blaze.Internal (preEscapedString)
|
||||||
#endif
|
#endif
|
||||||
import Text.Printf
|
import Text.Printf
|
||||||
import Text.JSON
|
|
||||||
|
|
||||||
import Hledger.Utils
|
import Hledger.Utils
|
||||||
import Hledger.Data
|
import Hledger.Data
|
||||||
@ -24,8 +23,6 @@ import Hledger.Reports
|
|||||||
import Hledger.Cli.Options
|
import Hledger.Cli.Options
|
||||||
import Hledger.Web.Options
|
import Hledger.Web.Options
|
||||||
|
|
||||||
import Handler.Utils
|
|
||||||
|
|
||||||
-------------------------------------------------------------------------------
|
-------------------------------------------------------------------------------
|
||||||
-- Common page layout
|
-- Common page layout
|
||||||
|
|
||||||
@ -124,121 +121,6 @@ searchform VD{..} = [hamlet|
|
|||||||
where
|
where
|
||||||
filtering = not $ null q
|
filtering = not $ null q
|
||||||
|
|
||||||
-- | Add transaction form.
|
|
||||||
addform :: Text -> ViewData -> HtmlUrl AppRoute
|
|
||||||
addform _ vd@VD{..} = [hamlet|
|
|
||||||
<script language="javascript">
|
|
||||||
jQuery(document).ready(function() {
|
|
||||||
|
|
||||||
/* set up type-ahead fields */
|
|
||||||
|
|
||||||
datesSuggester = new Bloodhound({
|
|
||||||
local:#{listToJsonValueObjArrayStr dates},
|
|
||||||
limit:100,
|
|
||||||
datumTokenizer: function(d) { return [d.value]; },
|
|
||||||
queryTokenizer: function(q) { return [q]; }
|
|
||||||
});
|
|
||||||
datesSuggester.initialize();
|
|
||||||
jQuery('#date').typeahead(
|
|
||||||
{
|
|
||||||
highlight: true
|
|
||||||
},
|
|
||||||
{
|
|
||||||
source: datesSuggester.ttAdapter()
|
|
||||||
}
|
|
||||||
);
|
|
||||||
|
|
||||||
accountsSuggester = new Bloodhound({
|
|
||||||
local:#{listToJsonValueObjArrayStr accts},
|
|
||||||
limit:100,
|
|
||||||
datumTokenizer: function(d) { return [d.value]; },
|
|
||||||
queryTokenizer: function(q) { return [q]; }
|
|
||||||
/*
|
|
||||||
datumTokenizer: Bloodhound.tokenizers.obj.whitespace('value'),
|
|
||||||
datumTokenizer: Bloodhound.tokenizers.whitespace(d.value)
|
|
||||||
queryTokenizer: Bloodhound.tokenizers.whitespace
|
|
||||||
*/
|
|
||||||
});
|
|
||||||
accountsSuggester.initialize();
|
|
||||||
jQuery('#account1,#account2').typeahead(
|
|
||||||
{
|
|
||||||
/* minLength: 3, */
|
|
||||||
highlight: true
|
|
||||||
},
|
|
||||||
{
|
|
||||||
source: accountsSuggester.ttAdapter()
|
|
||||||
}
|
|
||||||
);
|
|
||||||
|
|
||||||
descriptionsSuggester = new Bloodhound({
|
|
||||||
local:#{listToJsonValueObjArrayStr descriptions},
|
|
||||||
limit:100,
|
|
||||||
datumTokenizer: function(d) { return [d.value]; },
|
|
||||||
queryTokenizer: function(q) { return [q]; }
|
|
||||||
});
|
|
||||||
descriptionsSuggester.initialize();
|
|
||||||
jQuery('#description').typeahead(
|
|
||||||
{
|
|
||||||
highlight: true
|
|
||||||
},
|
|
||||||
{
|
|
||||||
source: descriptionsSuggester.ttAdapter()
|
|
||||||
}
|
|
||||||
);
|
|
||||||
|
|
||||||
});
|
|
||||||
|
|
||||||
<form#addform method=POST .collapse style="position:relative;">
|
|
||||||
<a role=button .btn .btn-lg .close style="position:absolute; top:-1.2em; right:0; padding-right:.1em; padding-top:.1em; font-size:24px;" title="Cancel" onclick="addformCancel()">×
|
|
||||||
<table.form style="width:100%; white-space:nowrap;">
|
|
||||||
<tr>
|
|
||||||
<td colspan=4>
|
|
||||||
<table style="width:100%;">
|
|
||||||
<tr#descriptionrow>
|
|
||||||
<td>
|
|
||||||
<input #date .form-control .input-lg type=text size=15 name=date placeholder="Date" value=#{date}>
|
|
||||||
<td>
|
|
||||||
<input #description .form-control .input-lg type=text size=40 name=description placeholder="Description">
|
|
||||||
$forall n <- postingnums
|
|
||||||
^{postingfields vd n}
|
|
||||||
|]
|
|
||||||
where
|
|
||||||
date = "today" :: String
|
|
||||||
dates = ["today","yesterday","tomorrow"] :: [String]
|
|
||||||
descriptions = sort $ nub $ map tdescription $ jtxns j
|
|
||||||
accts = sort $ journalAccountNamesUsed j
|
|
||||||
listToJsonValueObjArrayStr as = preEscapedString $ encode $ JSArray $ map (\a -> JSObject $ toJSObject [("value", showJSON a)]) as
|
|
||||||
numpostings = 2
|
|
||||||
postingnums = [1..numpostings]
|
|
||||||
postingfields :: ViewData -> Int -> HtmlUrl AppRoute
|
|
||||||
postingfields _ n = [hamlet|
|
|
||||||
<tr .posting .#{lastclass}>
|
|
||||||
<td style="padding-left:2em;">
|
|
||||||
<input ##{acctvar} .form-control .input-lg style="width:100%;" type=text name=#{acctvar} placeholder="#{acctph}">
|
|
||||||
^{amtfieldorsubmitbtn}
|
|
||||||
|]
|
|
||||||
where
|
|
||||||
islast = n == numpostings
|
|
||||||
lastclass = if islast then "lastrow" else "" :: String
|
|
||||||
acctvar = "account" ++ show n
|
|
||||||
acctph = "Account " ++ show n
|
|
||||||
amtfieldorsubmitbtn
|
|
||||||
| not islast = [hamlet|
|
|
||||||
<td>
|
|
||||||
<input ##{amtvar} .form-control .input-lg type=text size=10 name=#{amtvar} placeholder="#{amtph}">
|
|
||||||
|]
|
|
||||||
| otherwise = [hamlet|
|
|
||||||
<td #addbtncell style="text-align:right;">
|
|
||||||
<input type=hidden name=action value=add>
|
|
||||||
<button type=submit .btn .btn-lg name=submit>add
|
|
||||||
$if length files' > 1
|
|
||||||
<br>to: ^{journalselect files'}
|
|
||||||
|]
|
|
||||||
where
|
|
||||||
amtvar = "amount" ++ show n
|
|
||||||
amtph = "Amount " ++ show n
|
|
||||||
files' = [(takeFileName f,s) | (f,s) <- files j]
|
|
||||||
|
|
||||||
-- | Edit journal form.
|
-- | Edit journal form.
|
||||||
editform :: ViewData -> HtmlUrl AppRoute
|
editform :: ViewData -> HtmlUrl AppRoute
|
||||||
editform VD{..} = [hamlet|
|
editform VD{..} = [hamlet|
|
||||||
@ -285,13 +167,6 @@ importform = [hamlet|
|
|||||||
<a href="#" onclick="return importformToggle(event)">cancel
|
<a href="#" onclick="return importformToggle(event)">cancel
|
||||||
|]
|
|]
|
||||||
|
|
||||||
journalselect :: [(FilePath,String)] -> HtmlUrl AppRoute
|
|
||||||
journalselect journalfiles = [hamlet|
|
|
||||||
<select id=journalselect name=journal onchange="editformJournalSelect(event)">
|
|
||||||
$forall f <- journalfiles
|
|
||||||
<option value=#{fst f}>#{fst f}
|
|
||||||
|]
|
|
||||||
|
|
||||||
-- | Link to a topic in the manual.
|
-- | Link to a topic in the manual.
|
||||||
helplink :: String -> String -> HtmlUrl AppRoute
|
helplink :: String -> String -> HtmlUrl AppRoute
|
||||||
helplink topic label = [hamlet|
|
helplink topic label = [hamlet|
|
||||||
|
|||||||
@ -6,7 +6,6 @@ import Import
|
|||||||
|
|
||||||
import Handler.Common
|
import Handler.Common
|
||||||
import Handler.Post
|
import Handler.Post
|
||||||
import Handler.Utils
|
|
||||||
|
|
||||||
import Hledger.Data
|
import Hledger.Data
|
||||||
import Hledger.Query
|
import Hledger.Query
|
||||||
@ -19,7 +18,6 @@ import Hledger.Web.Options
|
|||||||
getJournalR :: Handler Html
|
getJournalR :: Handler Html
|
||||||
getJournalR = do
|
getJournalR = do
|
||||||
vd@VD{..} <- getViewData
|
vd@VD{..} <- getViewData
|
||||||
staticRootUrl <- (staticRoot . settings) <$> getYesod
|
|
||||||
let -- XXX like registerReportAsHtml
|
let -- XXX like registerReportAsHtml
|
||||||
inacct = inAccount qopts
|
inacct = inAccount qopts
|
||||||
-- injournal = isNothing inacct
|
-- injournal = isNothing inacct
|
||||||
@ -35,9 +33,7 @@ getJournalR = do
|
|||||||
hledgerLayout vd "journal" [hamlet|
|
hledgerLayout vd "journal" [hamlet|
|
||||||
<h2#contenttitle>#{title}
|
<h2#contenttitle>#{title}
|
||||||
<!-- p>Journal entries record movements of commodities between accounts. -->
|
<!-- p>Journal entries record movements of commodities between accounts. -->
|
||||||
<a#addformlink role="button" style="cursor:pointer;" onclick="addformToggle()" title="Add a new transaction to the journal" style="margin-top:1em;">Add transaction
|
<a#addformlink role="button" style="cursor:pointer;" data-toggle="modal" data-target="#addmodal" title="Add a new transaction to the journal" style="margin-top:1em;">Add a transaction
|
||||||
^{addform staticRootUrl vd}
|
|
||||||
<p>
|
|
||||||
^{maincontent}
|
^{maincontent}
|
||||||
|]
|
|]
|
||||||
|
|
||||||
|
|||||||
@ -13,7 +13,6 @@ import qualified Data.Text as T (null)
|
|||||||
import Text.Parsec (eof)
|
import Text.Parsec (eof)
|
||||||
import Text.Printf (printf)
|
import Text.Printf (printf)
|
||||||
|
|
||||||
import Handler.Utils
|
|
||||||
import Hledger.Utils
|
import Hledger.Utils
|
||||||
import Hledger.Data
|
import Hledger.Data
|
||||||
import Hledger.Read
|
import Hledger.Read
|
||||||
|
|||||||
@ -5,7 +5,6 @@ module Handler.SidebarR where
|
|||||||
import Import
|
import Import
|
||||||
|
|
||||||
import Handler.Common
|
import Handler.Common
|
||||||
import Handler.Utils
|
|
||||||
|
|
||||||
-- | Render just the accounts sidebar, useful when opening the sidebar.
|
-- | Render just the accounts sidebar, useful when opening the sidebar.
|
||||||
getSidebarR :: Handler Html
|
getSidebarR :: Handler Html
|
||||||
|
|||||||
@ -1,114 +1,14 @@
|
|||||||
-- | Web handler utilities.
|
-- | Web handler utilities. More of these are in Foundation.hs, where
|
||||||
|
-- they can be used in the default template.
|
||||||
|
|
||||||
module Handler.Utils where
|
module Handler.Utils where
|
||||||
|
|
||||||
import Prelude
|
import Prelude
|
||||||
import Control.Applicative ((<$>))
|
|
||||||
import Data.IORef
|
|
||||||
import Data.Maybe
|
|
||||||
import Data.Text(pack,unpack)
|
|
||||||
import Data.Time.Calendar
|
import Data.Time.Calendar
|
||||||
import Data.Time.Clock
|
import Data.Time.Clock
|
||||||
import Data.Time.Format
|
import Data.Time.Format
|
||||||
import System.Locale (defaultTimeLocale)
|
import System.Locale (defaultTimeLocale)
|
||||||
import Text.Hamlet
|
|
||||||
import Yesod.Core
|
|
||||||
|
|
||||||
import Foundation
|
|
||||||
|
|
||||||
import Hledger hiding (is)
|
|
||||||
import Hledger.Cli hiding (version)
|
|
||||||
import Hledger.Web.Options
|
|
||||||
|
|
||||||
|
|
||||||
-- | A bundle of data useful for hledger-web request handlers and templates.
|
|
||||||
data ViewData = VD {
|
|
||||||
opts :: WebOpts -- ^ the command-line options at startup
|
|
||||||
,here :: AppRoute -- ^ the current route
|
|
||||||
,msg :: Maybe Html -- ^ the current UI message if any, possibly from the current request
|
|
||||||
,today :: Day -- ^ today's date (for queries containing relative dates)
|
|
||||||
,j :: Journal -- ^ the up-to-date parsed unfiltered journal
|
|
||||||
,q :: String -- ^ the current q parameter, the main query expression
|
|
||||||
,m :: Query -- ^ a query parsed from the q parameter
|
|
||||||
,qopts :: [QueryOpt] -- ^ query options parsed from the q parameter
|
|
||||||
,am :: Query -- ^ a query parsed from the accounts sidebar query expr ("a" parameter)
|
|
||||||
,aopts :: [QueryOpt] -- ^ query options parsed from the accounts sidebar query expr
|
|
||||||
,showpostings :: Bool -- ^ current p parameter, 1 or 0 shows/hides all postings where applicable
|
|
||||||
,showsidebar :: Bool -- ^ current showsidebar cookie value
|
|
||||||
}
|
|
||||||
|
|
||||||
-- | Make a default ViewData, using day 0 as today's date.
|
|
||||||
nullviewdata :: ViewData
|
|
||||||
nullviewdata = viewdataWithDateAndParams nulldate "" "" ""
|
|
||||||
|
|
||||||
-- | Make a ViewData using the given date and request parameters, and defaults elsewhere.
|
|
||||||
viewdataWithDateAndParams :: Day -> String -> String -> String -> ViewData
|
|
||||||
viewdataWithDateAndParams d q a p =
|
|
||||||
let (querymatcher,queryopts) = parseQuery d q
|
|
||||||
(acctsmatcher,acctsopts) = parseQuery d a
|
|
||||||
in VD {
|
|
||||||
opts = defwebopts
|
|
||||||
,j = nulljournal
|
|
||||||
,here = RootR
|
|
||||||
,msg = Nothing
|
|
||||||
,today = d
|
|
||||||
,q = q
|
|
||||||
,m = querymatcher
|
|
||||||
,qopts = queryopts
|
|
||||||
,am = acctsmatcher
|
|
||||||
,aopts = acctsopts
|
|
||||||
,showpostings = p == "1"
|
|
||||||
,showsidebar = False
|
|
||||||
}
|
|
||||||
|
|
||||||
-- | Gather data used by handlers and templates in the current request.
|
|
||||||
getViewData :: Handler ViewData
|
|
||||||
getViewData = do
|
|
||||||
app <- getYesod
|
|
||||||
let opts@WebOpts{cliopts_=copts@CliOpts{reportopts_=ropts}} = appOpts app
|
|
||||||
(j, err) <- getCurrentJournal app copts{reportopts_=ropts{no_elide_=True}}
|
|
||||||
msg <- getMessageOr err
|
|
||||||
Just here <- getCurrentRoute
|
|
||||||
today <- liftIO getCurrentDay
|
|
||||||
q <- getParameterOrNull "q"
|
|
||||||
a <- getParameterOrNull "a"
|
|
||||||
p <- getParameterOrNull "p"
|
|
||||||
cookies <- reqCookies <$> getRequest
|
|
||||||
let showsidebar = maybe False (=="1") $ lookup "showsidebar" cookies
|
|
||||||
return (viewdataWithDateAndParams today q a p){
|
|
||||||
opts=opts
|
|
||||||
,msg=msg
|
|
||||||
,here=here
|
|
||||||
,today=today
|
|
||||||
,j=j
|
|
||||||
,showsidebar=showsidebar
|
|
||||||
}
|
|
||||||
where
|
|
||||||
-- | Update our copy of the journal if the file changed. If there is an
|
|
||||||
-- error while reloading, keep the old one and return the error, and set a
|
|
||||||
-- ui message.
|
|
||||||
getCurrentJournal :: App -> CliOpts -> Handler (Journal, Maybe String)
|
|
||||||
getCurrentJournal app opts = do
|
|
||||||
-- XXX put this inside atomicModifyIORef' for thread safety
|
|
||||||
j <- liftIO $ readIORef $ appJournal app
|
|
||||||
(jE, changed) <- liftIO $ journalReloadIfChanged opts j
|
|
||||||
if not changed
|
|
||||||
then return (j,Nothing)
|
|
||||||
else case jE of
|
|
||||||
Right j' -> do liftIO $ writeIORef (appJournal app) j'
|
|
||||||
return (j',Nothing)
|
|
||||||
Left e -> do setMessage $ "error while reading" {- ++ ": " ++ e-}
|
|
||||||
return (j, Just e)
|
|
||||||
|
|
||||||
-- | Get the named request parameter, or the empty string if not present.
|
|
||||||
getParameterOrNull :: String -> Handler String
|
|
||||||
getParameterOrNull p = unpack `fmap` fromMaybe "" <$> lookupGetParam (pack p)
|
|
||||||
|
|
||||||
-- | Get the message set by the last request, or the newer message provided, if any.
|
|
||||||
getMessageOr :: Maybe String -> Handler (Maybe Html)
|
|
||||||
getMessageOr mnewmsg = do
|
|
||||||
oldmsg <- getMessage
|
|
||||||
return $ maybe oldmsg (Just . toHtml) mnewmsg
|
|
||||||
|
|
||||||
numbered :: [a] -> [(Int,a)]
|
numbered :: [a] -> [(Int,a)]
|
||||||
numbered = zip [1..]
|
numbered = zip [1..]
|
||||||
|
|||||||
@ -11,13 +11,11 @@
|
|||||||
// else if ($.url.param('sidebar')=='1')
|
// else if ($.url.param('sidebar')=='1')
|
||||||
// $('#sidebar').show();
|
// $('#sidebar').show();
|
||||||
|
|
||||||
if ($.url.param('add')) {
|
|
||||||
$('#addform').collapse('show');
|
|
||||||
$('#addform input[name=description]').focus();
|
|
||||||
}
|
|
||||||
|
|
||||||
$(document).ready(function() {
|
$(document).ready(function() {
|
||||||
|
|
||||||
|
/* show add form if ?add=1 */
|
||||||
|
if ($.url.param('add')) { addformShow(); }
|
||||||
|
|
||||||
/* sidebar account hover handlers */
|
/* sidebar account hover handlers */
|
||||||
$('#sidebar td a').mouseenter(function(){ $(this).parent().addClass('mouseover'); });
|
$('#sidebar td a').mouseenter(function(){ $(this).parent().addClass('mouseover'); });
|
||||||
$('#sidebar td').mouseleave(function(){ $(this).removeClass('mouseover'); });
|
$('#sidebar td').mouseleave(function(){ $(this).removeClass('mouseover'); });
|
||||||
@ -27,8 +25,7 @@ $(document).ready(function() {
|
|||||||
$(document).bind('keydown', 'h', function(){ $('#helpmodal').modal('toggle'); return false; });
|
$(document).bind('keydown', 'h', function(){ $('#helpmodal').modal('toggle'); return false; });
|
||||||
$(document).bind('keydown', 'j', function(){ location.href = '/journal'; return false; });
|
$(document).bind('keydown', 'j', function(){ location.href = '/journal'; return false; });
|
||||||
$(document).bind('keydown', 's', function(){ sidebarToggle(); return false; });
|
$(document).bind('keydown', 's', function(){ sidebarToggle(); return false; });
|
||||||
$(document).bind('keydown', 'a', function(){ addformFocus(); return false; });
|
$(document).bind('keydown', 'a', function(){ addformShow(); return false; });
|
||||||
$('#addform input,#addform button,#addformlink').bind('keydown', 'esc', addformCancel);
|
|
||||||
$(document).bind('keydown', '/', function(){ $('#searchform input').focus(); return false; });
|
$(document).bind('keydown', '/', function(){ $('#searchform input').focus(); return false; });
|
||||||
$('#addform input,#addform button,#addformlink').bind('keydown', 'ctrl+shift+=', addformAddPosting);
|
$('#addform input,#addform button,#addformlink').bind('keydown', 'ctrl+shift+=', addformAddPosting);
|
||||||
$('#addform input,#addform button,#addformlink').bind('keydown', 'ctrl+=', addformAddPosting);
|
$('#addform input,#addform button,#addformlink').bind('keydown', 'ctrl+=', addformAddPosting);
|
||||||
@ -67,33 +64,10 @@ function sidebarToggle() {
|
|||||||
$('#sidebar').animate({'width': visible ? 'hide' : 'show'});
|
$('#sidebar').animate({'width': visible ? 'hide' : 'show'});
|
||||||
}
|
}
|
||||||
|
|
||||||
function addformToggle() {
|
function addformShow() {
|
||||||
if (location.pathname != '/journal') {
|
$('#addmodal').modal('show').on('shown.bs.modal', function (e) {
|
||||||
location.href = '/journal?add=1';
|
$('#addform input[name=date]').focus();
|
||||||
}
|
});
|
||||||
else {
|
|
||||||
$('#addform').collapse('toggle');
|
|
||||||
$('#addform input[name=description]').focus();
|
|
||||||
}
|
|
||||||
}
|
|
||||||
|
|
||||||
function addformFocus() {
|
|
||||||
if (location.pathname != '/journal') {
|
|
||||||
location.href = '/journal?add=1';
|
|
||||||
}
|
|
||||||
else {
|
|
||||||
$('#addform').collapse('show');
|
|
||||||
$('#addform input[name=description]').focus();
|
|
||||||
}
|
|
||||||
}
|
|
||||||
|
|
||||||
function addformCancel() {
|
|
||||||
$('#addform input[type=text]').typeahead('val','');
|
|
||||||
$('#addform')
|
|
||||||
.each( function(){ this.reset();} )
|
|
||||||
.collapse('hide');
|
|
||||||
// try to keep keybindings working in safari
|
|
||||||
//$('#addformlink').focus();
|
|
||||||
}
|
}
|
||||||
|
|
||||||
function addformAddPosting() {
|
function addformAddPosting() {
|
||||||
|
|||||||
@ -92,3 +92,12 @@ $newline never
|
|||||||
<li> Prepend <b><tt>not:</tt></b> to negate a search term
|
<li> Prepend <b><tt>not:</tt></b> to negate a search term
|
||||||
<li> Multiple search terms on different fields are AND'ed, multiple search terms on the same field are OR'ed
|
<li> Multiple search terms on different fields are AND'ed, multiple search terms on the same field are OR'ed
|
||||||
<li> These search terms also work with command-line hledger
|
<li> These search terms also work with command-line hledger
|
||||||
|
|
||||||
|
<div .modal #addmodal tabindex="-1" role="dialog" aria-labelledby="addLabel" aria-hidden="true">
|
||||||
|
<div .modal-dialog .modal-lg>
|
||||||
|
<div .modal-content>
|
||||||
|
<div .modal-header>
|
||||||
|
<button type="button" .close data-dismiss="modal" aria-hidden="true">×
|
||||||
|
<h3 .modal-title #addLabel>Add a transaction
|
||||||
|
<div .modal-body>
|
||||||
|
^{addform staticRootUrl vd}
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user