web: a bunch of ui cleanup & improvement
- the web UI has been streamlined; edit form, raw & entries views dropped - we now remember whether sidebar is open or closed - better help dialog - keyboard shortcuts are now available - better add form - more bootstrap styling - static file cleanups - report filtering fixes - upgrade jquery to 2.1.1, bootstrap to 3.1.1, drop select2, add typeahead, cookie, hotkeys - clarify debug helpers a little - refactoring
This commit is contained in:
		
							parent
							
								
									34f4800e82
								
							
						
					
					
						commit
						ec51d28839
					
				| @ -1,7 +1,10 @@ | |||||||
| {-# LANGUAGE RecordWildCards, DeriveDataTypeable, FlexibleInstances #-} | {-# LANGUAGE RecordWildCards, DeriveDataTypeable, FlexibleInstances #-} | ||||||
| {-| | {-| | ||||||
| 
 | 
 | ||||||
| Whole-journal, account-centric, and per-commodity transactions reports, used by hledger-web. | Here are several variants of a transactions report. | ||||||
|  | Transactions reports are like a postings report, but more | ||||||
|  | transaction-oriented, and (in the account-centric variant) relative to | ||||||
|  | a some base account.  They are used by hledger-web. | ||||||
| 
 | 
 | ||||||
| -} | -} | ||||||
| 
 | 
 | ||||||
| @ -58,13 +61,15 @@ triSimpleBalance (_,_,_,_,_,Mixed a) = case a of [] -> "0" | |||||||
| 
 | 
 | ||||||
| -- | Select transactions from the whole journal. This is similar to a | -- | Select transactions from the whole journal. This is similar to a | ||||||
| -- "postingsReport" except with transaction-based report items which | -- "postingsReport" except with transaction-based report items which | ||||||
| -- are ordered most recent first. This is used by eg hledger-web's journal view. | -- are ordered most recent first. XXX Or an EntriesReport - use that instead ? | ||||||
|  | -- This is used by hledger-web's journal view. | ||||||
| journalTransactionsReport :: ReportOpts -> Journal -> Query -> TransactionsReport | journalTransactionsReport :: ReportOpts -> Journal -> Query -> TransactionsReport | ||||||
| journalTransactionsReport _ Journal{jtxns=ts} m = (totallabel, items) | journalTransactionsReport opts j q = (totallabel, items) | ||||||
|    where |    where | ||||||
|      ts' = sortBy (comparing tdate) $ filter (not . null . tpostings) $ map (filterTransactionPostings m) ts |  | ||||||
|      items = reverse $ accountTransactionsReportItems m Nothing nullmixedamt id ts' |  | ||||||
|      -- XXX items' first element should be the full transaction with all postings |      -- XXX items' first element should be the full transaction with all postings | ||||||
|  |      items = reverse $ accountTransactionsReportItems q Nothing nullmixedamt id ts | ||||||
|  |      ts    = sortBy (comparing date) $ filter (q `matchesTransaction`) $ jtxns $ journalSelectingAmountFromOpts opts j | ||||||
|  |      date  = transactionDateFn opts | ||||||
| 
 | 
 | ||||||
| ------------------------------------------------------------------------------- | ------------------------------------------------------------------------------- | ||||||
| 
 | 
 | ||||||
| @ -83,16 +88,20 @@ journalTransactionsReport _ Journal{jtxns=ts} m = (totallabel, items) | |||||||
| -- reporting intervals are not supported, and report items are most | -- reporting intervals are not supported, and report items are most | ||||||
| -- recent first. | -- recent first. | ||||||
| accountTransactionsReport :: ReportOpts -> Journal -> Query -> Query -> TransactionsReport | accountTransactionsReport :: ReportOpts -> Journal -> Query -> Query -> TransactionsReport | ||||||
| accountTransactionsReport opts j m thisacctquery = (label, items) | accountTransactionsReport opts j q thisacctquery = (label, items) | ||||||
|  where |  where | ||||||
|      -- transactions affecting this account, in date order |      -- transactions affecting this account, in date order | ||||||
|      ts = sortBy (comparing tdate) $ filter (matchesTransaction thisacctquery) $ jtxns $ |      curq = filterQuery queryIsSym q | ||||||
|  |      ts = sortBy (comparing tdate) $ | ||||||
|  |           filter (matchesTransaction thisacctquery) $ | ||||||
|  |           jtxns $ | ||||||
|  |           filterJournalAmounts curq $ | ||||||
|           journalSelectingAmountFromOpts opts j |           journalSelectingAmountFromOpts opts j | ||||||
|      -- starting balance: if we are filtering by a start date and nothing else, |      -- starting balance: if we are filtering by a start date and nothing else, | ||||||
|      -- the sum of postings to this account before that date; otherwise zero. |      -- the sum of postings to this account before that date; otherwise zero. | ||||||
|      (startbal,label) | queryIsNull m                           = (nullmixedamt,        balancelabel) |      (startbal,label) | queryIsNull q                        = (nullmixedamt,        balancelabel) | ||||||
|                       | queryIsStartDateOnly (date2_ opts) m = (sumPostings priorps, balancelabel) |                       | queryIsStartDateOnly (date2_ opts) q = (sumPostings priorps, balancelabel) | ||||||
|                       | otherwise                                 = (nullmixedamt,        totallabel) |                       | otherwise                            = (nullmixedamt,        totallabel) | ||||||
|                       where |                       where | ||||||
|                         priorps = -- ltrace "priorps" $ |                         priorps = -- ltrace "priorps" $ | ||||||
|                                   filter (matchesPosting |                                   filter (matchesPosting | ||||||
| @ -100,8 +109,8 @@ accountTransactionsReport opts j m thisacctquery = (label, items) | |||||||
|                                            And [thisacctquery, tostartdatequery])) |                                            And [thisacctquery, tostartdatequery])) | ||||||
|                                          $ transactionsPostings ts |                                          $ transactionsPostings ts | ||||||
|                         tostartdatequery = Date (DateSpan Nothing startdate) |                         tostartdatequery = Date (DateSpan Nothing startdate) | ||||||
|                         startdate = queryStartDate (date2_ opts) m |                         startdate = queryStartDate (date2_ opts) q | ||||||
|      items = reverse $ accountTransactionsReportItems m (Just thisacctquery) startbal negate ts |      items = reverse $ accountTransactionsReportItems q (Just thisacctquery) startbal negate ts | ||||||
| 
 | 
 | ||||||
| totallabel = "Total" | totallabel = "Total" | ||||||
| balancelabel = "Balance" | balancelabel = "Balance" | ||||||
| @ -122,10 +131,9 @@ accountTransactionsReportItems query thisacctquery bal signfn (t:ts) = | |||||||
|                                                        Nothing -> ([],psmatched) |                                                        Nothing -> ([],psmatched) | ||||||
|       numotheraccts = length $ nub $ map paccount psotheracct |       numotheraccts = length $ nub $ map paccount psotheracct | ||||||
|       amt = negate $ sum $ map pamount psthisacct |       amt = negate $ sum $ map pamount psthisacct | ||||||
|       acct | isNothing thisacctquery = summarisePostings psmatched -- journal register |       acct | isNothing thisacctquery = summarisePostingAccounts psmatched | ||||||
|            | numotheraccts == 0 = "transfer between " ++ summarisePostingAccounts psthisacct |            | numotheraccts == 0      = summarisePostingAccounts psthisacct | ||||||
|            | otherwise          = prefix              ++ summarisePostingAccounts psotheracct |            | otherwise               = summarisePostingAccounts psotheracct | ||||||
|            where prefix = maybe "" (\b -> if b then "from " else "to ") $ isNegativeMixedAmount amt |  | ||||||
|       (i,bal') = case psmatched of |       (i,bal') = case psmatched of | ||||||
|            [] -> (Nothing,bal) |            [] -> (Nothing,bal) | ||||||
|            _  -> (Just (t, tmatched, numotheraccts > 1, acct, a, b), b) |            _  -> (Just (t, tmatched, numotheraccts > 1, acct, a, b), b) | ||||||
|  | |||||||
| @ -450,10 +450,16 @@ dbg2 = dbgAt 2 | |||||||
| dbgAt :: Show a => Int -> String -> a -> a | dbgAt :: Show a => Int -> String -> a -> a | ||||||
| dbgAt lvl = dbgppshow lvl | dbgAt lvl = dbgppshow lvl | ||||||
| 
 | 
 | ||||||
|  | -- dbgAtM :: (Monad m, Show a) => Int -> String -> a -> m a | ||||||
|  | -- dbgAtM lvl lbl x = dbgAt lvl lbl x `seq` return x | ||||||
|  | -- XXX | ||||||
| dbgAtM :: Show a => Int -> String -> a -> IO () | dbgAtM :: Show a => Int -> String -> a -> IO () | ||||||
| dbgAtM lvl lbl x = dbgAt lvl lbl x `seq` return () | dbgAtM = dbgAtIO | ||||||
| 
 | 
 | ||||||
| -- | Print this string to the console before evaluating the expression, | dbgAtIO :: Show a => Int -> String -> a -> IO () | ||||||
|  | dbgAtIO lvl lbl x = dbgAt lvl lbl x `seq` return () | ||||||
|  | 
 | ||||||
|  | -- | print this string to the console before evaluating the expression, | ||||||
| -- if the global debug level is non-zero.  Uses unsafePerformIO. | -- if the global debug level is non-zero.  Uses unsafePerformIO. | ||||||
| dbgtrace :: String -> a -> a | dbgtrace :: String -> a -> a | ||||||
| dbgtrace | dbgtrace | ||||||
|  | |||||||
| @ -31,9 +31,8 @@ import Network.HTTP.Conduit (def) | |||||||
| -- 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 | ||||||
| import Handler.JournalR | import Handler.JournalR | ||||||
| import Handler.JournalEditR |  | ||||||
| import Handler.JournalEntriesR |  | ||||||
| import Handler.RegisterR | import Handler.RegisterR | ||||||
|  | import Handler.SidebarR | ||||||
| 
 | 
 | ||||||
| import Hledger.Web.Options (WebOpts(..), defwebopts) | import Hledger.Web.Options (WebOpts(..), defwebopts) | ||||||
| import Hledger.Data (Journal, nulljournal) | import Hledger.Data (Journal, nulljournal) | ||||||
|  | |||||||
| @ -104,13 +104,18 @@ instance Yesod App where | |||||||
|         pc <- widgetToPageContent $ do |         pc <- widgetToPageContent $ do | ||||||
|             $(widgetFile "normalize") |             $(widgetFile "normalize") | ||||||
|             addStylesheet $ StaticR css_bootstrap_min_css |             addStylesheet $ StaticR css_bootstrap_min_css | ||||||
|             -- load jquery early: |              -- load these things early, in HEAD: | ||||||
|             toWidgetHead [hamlet| <script type="text/javascript" src="@{StaticR js_jquery_min_js}"></script> |] |             toWidgetHead [hamlet| | ||||||
|  |                           <script type="text/javascript" src="@{StaticR js_jquery_min_js}"></script> | ||||||
|  |                           <script type="text/javascript" src="@{StaticR js_typeahead_bundle_min_js}"></script> | ||||||
|  |                          |] | ||||||
|  |             addScript $ StaticR js_bootstrap_min_js | ||||||
|  |             -- addScript $ StaticR js_typeahead_bundle_min_js | ||||||
|             addScript $ StaticR js_jquery_url_js |             addScript $ StaticR js_jquery_url_js | ||||||
|  |             addScript $ StaticR js_jquery_cookie_js | ||||||
|  |             addScript $ StaticR js_jquery_hotkeys_js | ||||||
|             addScript $ StaticR js_jquery_flot_min_js |             addScript $ StaticR js_jquery_flot_min_js | ||||||
|             toWidget [hamlet| \<!--[if lte IE 8]> <script type="text/javascript" src="@{StaticR js_excanvas_min_js}"></script> <![endif]--> |] |             toWidget [hamlet| \<!--[if lte IE 8]> <script type="text/javascript" src="@{StaticR js_excanvas_min_js}"></script> <![endif]--> |] | ||||||
|             addScript $ StaticR select2_min_js |  | ||||||
|             addStylesheet $ StaticR select2_css |  | ||||||
|             addStylesheet $ StaticR hledger_css |             addStylesheet $ StaticR hledger_css | ||||||
|             addScript $ StaticR hledger_js |             addScript $ StaticR hledger_js | ||||||
|             $(widgetFile "default-layout") |             $(widgetFile "default-layout") | ||||||
|  | |||||||
| @ -6,7 +6,6 @@ module Handler.Common where | |||||||
| import Import | import Import | ||||||
| 
 | 
 | ||||||
| import Data.List | import Data.List | ||||||
| import Data.Maybe |  | ||||||
| import Data.Text(pack) | import Data.Text(pack) | ||||||
| import Data.Time.Calendar | import Data.Time.Calendar | ||||||
| import System.FilePath (takeFileName) | import System.FilePath (takeFileName) | ||||||
| @ -28,20 +27,39 @@ import Hledger.Web.Options | |||||||
| import Handler.Utils | import Handler.Utils | ||||||
| 
 | 
 | ||||||
| ------------------------------------------------------------------------------- | ------------------------------------------------------------------------------- | ||||||
| -- Page components | -- Common page layout | ||||||
|  | 
 | ||||||
|  | -- | Standard hledger-web page layout. | ||||||
|  | hledgerLayout :: ViewData -> String -> HtmlUrl AppRoute -> HandlerT App IO Html | ||||||
|  | hledgerLayout vd title content = do | ||||||
|  |   defaultLayout $ do | ||||||
|  |       setTitle $ toHtml $ title ++ " - hledger-web" | ||||||
|  |       toWidget [hamlet| | ||||||
|  |         <div#content> | ||||||
|  |          $if showsidebar vd | ||||||
|  |           <div#sidebar> | ||||||
|  |            <div#sidebar-spacer> | ||||||
|  |            <div#sidebar-body> | ||||||
|  |             ^{sidebar vd} | ||||||
|  |          $else | ||||||
|  |           <div#sidebar style="display:none;"> | ||||||
|  |            <div#sidebar-spacer> | ||||||
|  |            <div#sidebar-body> | ||||||
|  |          <div#main> | ||||||
|  |           ^{topbar vd} | ||||||
|  |           <div#maincontent> | ||||||
|  |            ^{searchform vd} | ||||||
|  |            ^{content} | ||||||
|  |       |] | ||||||
| 
 | 
 | ||||||
| -- | Global toolbar/heading area. | -- | Global toolbar/heading area. | ||||||
| topbar :: ViewData -> HtmlUrl AppRoute | topbar :: ViewData -> HtmlUrl AppRoute | ||||||
| topbar VD{..} = [hamlet| | topbar VD{..} = [hamlet| | ||||||
| <div#topbar> | <nav class="navbar" role="navigation"> | ||||||
|  <a.topleftlink href=#{hledgerorgurl} title="More about hledger"> |  <div#topbar> | ||||||
|   hledger-web |   <h1>#{title} | ||||||
|   <br /> |  $maybe m' <- msg | ||||||
|   \#{version} |   <div#message>#{m'} | ||||||
|  <a.toprightlink href=#{manualurl} target=hledgerhelp title="User manual">manual |  | ||||||
|  <h1>#{title} |  | ||||||
| $maybe m' <- msg |  | ||||||
|  <div#message>#{m'} |  | ||||||
| |] | |] | ||||||
|   where |   where | ||||||
|     title = takeFileName $ journalFilePath j |     title = takeFileName $ journalFilePath j | ||||||
| @ -50,19 +68,24 @@ $maybe m' <- msg | |||||||
| sidebar :: ViewData -> HtmlUrl AppRoute | sidebar :: ViewData -> HtmlUrl AppRoute | ||||||
| sidebar vd@VD{..} = | sidebar vd@VD{..} = | ||||||
|  [hamlet| |  [hamlet| | ||||||
|  <a#sidebar-toggle-link.togglelink href="#" title="Toggle sidebar">[+] |  <a.btn .btn-default role=button href=@{JournalR} title="Go back to top"> | ||||||
|  |   hledger-web | ||||||
|  |   <br /> | ||||||
|  |   \#{version} | ||||||
|  |  <p> | ||||||
|  |  <!-- | ||||||
|  |  <a#sidebartogglebtn role="button" style="cursor:pointer;" onclick="sidebarToggle()" title="Show/hide sidebar"> | ||||||
|  |   <span class="glyphicon glyphicon-expand"></span> | ||||||
|  |  --> | ||||||
|  |  <br> | ||||||
|  <div#sidebar-content> |  <div#sidebar-content> | ||||||
| 
 |  | ||||||
|   <p style="margin-top:1em;"> |   <p style="margin-top:1em;"> | ||||||
|    <a#addformlink href="#" onclick="return addformToggle(event)" title="Add a new transaction to the journal" style="margin-top:1em;">Add a transaction.. |    <a href=@{JournalR} .#{journalcurrent} title="Show general journal entries, most recent first" style="white-space:nowrap;">Journal | ||||||
| 
 |   <div#accounts style="margin-top:1em;"> | ||||||
|   <p style="margin-top:1em;"> |  | ||||||
|    <a href=@{JournalR} title="Show transactions in all accounts, most recent first">All accounts |  | ||||||
| 
 |  | ||||||
|   <div#accounts style="margin-top:.5em;"> |  | ||||||
|    ^{accounts} |    ^{accounts} | ||||||
| |] | |] | ||||||
|  where |  where | ||||||
|  |   journalcurrent = if here == JournalR then "current" else "" :: String | ||||||
|   accounts = balanceReportAsHtml opts vd $ balanceReport (reportopts_ $ cliopts_ opts){empty_=True} am j |   accounts = balanceReportAsHtml opts vd $ balanceReport (reportopts_ $ cliopts_ opts){empty_=True} am j | ||||||
| 
 | 
 | ||||||
| -- -- | Navigation link, preserving parameters and possibly highlighted. | -- -- | Navigation link, preserving parameters and possibly highlighted. | ||||||
| @ -90,38 +113,13 @@ searchform VD{..} = [hamlet| | |||||||
|  <form#searchform.form method=GET> |  <form#searchform.form method=GET> | ||||||
|   <table width="100%"> |   <table width="100%"> | ||||||
|    <tr> |    <tr> | ||||||
|     <td width="99%"> |     <td width="99%" style="position:relative;"> | ||||||
|      <input name=q value=#{q} style="width:98%;"> |  | ||||||
|     <td width="1%"> |  | ||||||
|      <input type=submit value="Search"> |  | ||||||
|    <tr valign=top> |  | ||||||
|     <td colspan=2 style="text-align:right;"> |  | ||||||
|      $if filtering |      $if filtering | ||||||
|       \ # |       <a role=button .btn .close style="position:absolute; right:0; padding-right:.1em; padding-left:.1em; margin-right:.1em; margin-left:.1em; font-size:24px;" href="@{here}" title="Clear search terms">× | ||||||
|       <span.showall> |      <input .form-control style="font-size:18px; padding-bottom:2px;" name=q value=#{q} title="Enter hledger search patterns to filter the data below"> | ||||||
|        <a href=@{here}>clear |     <td width="1%" style="white-space:nowrap;"> | ||||||
|      \ # |      <button .btn style="font-size:18px;" type=submit title="Apply search terms">Search | ||||||
|      <a#search-help-link href="#" title="Toggle search help">help |      <button .btn style="font-size:18px;" type=button data-toggle="modal" data-target="#searchhelpmodal" title="Show search and general help">? | ||||||
|    <tr> |  | ||||||
|     <td colspan=2> |  | ||||||
|      <div#search-help.help style="display:none;"> |  | ||||||
|       Leave blank to see journal (all transactions), or click account links to see transactions under that account. |  | ||||||
|       <br> |  | ||||||
|       Transactions/postings may additionally be filtered by |  | ||||||
|       acct:REGEXP (target account), # |  | ||||||
|       code:REGEXP (transaction code), # |  | ||||||
|       desc:REGEXP (description), # |  | ||||||
|       date:PERIODEXP (date), # |  | ||||||
|       date2:PERIODEXP (secondary date), # |  | ||||||
|       tag:TAG[=REGEX] (tag and optionally tag value), # |  | ||||||
|       depth:N (accounts at or above this depth), # |  | ||||||
|       status:*, status:!, status:  (cleared status), # |  | ||||||
|       real:BOOL (real/virtual-ness), # |  | ||||||
|       empty:BOOL (is amount zero), # |  | ||||||
|       amt:N, amt:<N, amt:>N (test magnitude of single-commodity amount). |  | ||||||
|       sym:REGEXP (commodity symbol), # |  | ||||||
|       <br> |  | ||||||
|       Prepend not: to negate, enclose multi-word patterns in quotes, multiple search terms are AND'ed. |  | ||||||
| |] | |] | ||||||
|  where |  where | ||||||
|   filtering = not $ null q |   filtering = not $ null q | ||||||
| @ -129,109 +127,117 @@ searchform VD{..} = [hamlet| | |||||||
| -- | Add transaction form. | -- | Add transaction form. | ||||||
| addform :: Text -> ViewData -> HtmlUrl AppRoute | addform :: Text -> ViewData -> HtmlUrl AppRoute | ||||||
| addform _ vd@VD{..} = [hamlet| | addform _ vd@VD{..} = [hamlet| | ||||||
| <script type=text/javascript> | <script language="javascript"> | ||||||
|  \$(document).ready(function() { |   jQuery(document).ready(function() { | ||||||
|     /* select2 setup */ |  | ||||||
|     var param = { |  | ||||||
|       "width": "250px", |  | ||||||
|       "openOnEnter": false, |  | ||||||
|       // createSearchChoice allows to create new values not in the options |  | ||||||
|       "createSearchChoice":function(term, data) { |  | ||||||
|         if ( $(data).filter( function() { |  | ||||||
|                 return this.text.localeCompare(term)===0; |  | ||||||
|                 }).length===0) { |  | ||||||
|           return {text:term}; |  | ||||||
|         } |  | ||||||
|       }, |  | ||||||
|       // id is what is passed during post |  | ||||||
|       "id": function(object) { |  | ||||||
|         return object.text; |  | ||||||
|       } |  | ||||||
|     }; |  | ||||||
|     \$("#description").select2($.extend({}, param, {data: #{toSelectData descriptions} })); |  | ||||||
|     var accountData = $.extend({}, param, {data: #{toSelectData acctnames} }); |  | ||||||
|     \$("#account1").select2(accountData); |  | ||||||
|     \$("#account2").select2(accountData); |  | ||||||
|  }); |  | ||||||
| 
 | 
 | ||||||
| <form#addform method=POST style=display:none;> |     /* set up type-ahead fields */ | ||||||
|   <h2#contenttitle>#{title} | 
 | ||||||
|   <table.form> |     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> |    <tr> | ||||||
|     <td colspan=4> |     <td colspan=4> | ||||||
|      <table> |      <table style="width:100%;"> | ||||||
|       <tr#descriptionrow> |       <tr#descriptionrow> | ||||||
|        <td> |        <td> | ||||||
|         Date: |         <input #date        .form-control .input-lg type=text size=15 name=date placeholder="Date" value=#{date}> | ||||||
|        <td> |        <td> | ||||||
|         <input.textinput size=15 name=date value=#{date}> |         <input #description .form-control .input-lg type=text size=40 name=description placeholder="Description"> | ||||||
|        <td style=padding-left:1em;> |    $forall n <- postingnums | ||||||
|         Description: |     ^{postingfields vd n} | ||||||
|        <td> |  | ||||||
|         <input type=hidden id=description name=description> |  | ||||||
|       <tr.helprow> |  | ||||||
|        <td> |  | ||||||
|        <td> |  | ||||||
|         <span.help>#{datehelp} # |  | ||||||
|        <td> |  | ||||||
|        <td> |  | ||||||
|         <span.help>#{deschelp} |  | ||||||
|    ^{postingfields vd 1} |  | ||||||
|    ^{postingfields vd 2} |  | ||||||
|    <tr#addbuttonrow> |  | ||||||
|     <td colspan=4> |  | ||||||
|      <input type=hidden name=action value=add> |  | ||||||
|      <input type=submit name=submit value="add transaction"> |  | ||||||
|      $if manyfiles |  | ||||||
|       \ to: ^{journalselect $ files j} |  | ||||||
|      \ or # |  | ||||||
|      <a href="#" onclick="return addformToggle(event)">cancel |  | ||||||
| |] | |] | ||||||
|  where |  where | ||||||
|   title = "Add transaction" :: String |  | ||||||
|   datehelp = "eg: 2010/7/20" :: String |  | ||||||
|   deschelp = "eg: supermarket (optional)" :: String |  | ||||||
|   date = "today" :: String |   date = "today" :: String | ||||||
|  |   dates = ["today","yesterday","tomorrow"] :: [String] | ||||||
|   descriptions = sort $ nub $ map tdescription $ jtxns j |   descriptions = sort $ nub $ map tdescription $ jtxns j | ||||||
|   acctnames = sort $ journalAccountNamesUsed j |   accts = sort $ journalAccountNamesUsed j | ||||||
|   -- Construct data for select2. Text must be quoted in a json string. |   listToJsonValueObjArrayStr as  = preEscapedString $ encode $ JSArray $ map (\a -> JSObject $ toJSObject [("value", showJSON a)]) as | ||||||
|   toSelectData as  = preEscapedString $ encode $ JSArray $ map (\a -> JSObject $ toJSObject [("text", showJSON a)]) as |   numpostings = 2 | ||||||
|   manyfiles = length (files j) > 1 |   postingnums = [1..numpostings] | ||||||
|   postingfields :: ViewData -> Int -> HtmlUrl AppRoute |   postingfields :: ViewData -> Int -> HtmlUrl AppRoute | ||||||
|   postingfields _ n = [hamlet| |   postingfields _ n = [hamlet| | ||||||
| <tr#postingrow> | <tr .posting .#{lastclass}> | ||||||
|  <td align=right>#{acctlabel}: |  <td style="padding-left:2em;"> | ||||||
|  <td> |   <input ##{acctvar} .form-control .input-lg style="width:100%;" type=text name=#{acctvar} placeholder="#{acctph}"> | ||||||
|   <input type=hidden id=#{acctvar} name=#{acctvar}> |  ^{amtfieldorsubmitbtn} | ||||||
|  ^{amtfield} |  | ||||||
| <tr.helprow> |  | ||||||
|  <td> |  | ||||||
|  <td> |  | ||||||
|   <span.help>#{accthelp} |  | ||||||
|  <td> |  | ||||||
|  <td> |  | ||||||
|   <span.help>#{amthelp} |  | ||||||
| |] | |] | ||||||
|    where |    where | ||||||
|     withnumber = (++ show n) |     islast = n == numpostings | ||||||
|     acctvar = withnumber "account" |     lastclass = if islast then "lastrow" else "" :: String | ||||||
|     amtvar = withnumber "amount" |     acctvar = "account" ++ show n | ||||||
|     (acctlabel, accthelp, amtfield, amthelp) |     acctph = "Account " ++ show n | ||||||
|        | n == 1     = ("To account" |     amtfieldorsubmitbtn | ||||||
|                      ,"eg: expenses:food" |        | not islast = [hamlet| | ||||||
|                      ,[hamlet| |           <td> | ||||||
| <td style=padding-left:1em;> |            <input ##{amtvar} .form-control .input-lg type=text size=10 name=#{amtvar} placeholder="#{amtph}"> | ||||||
|  Amount: |          |] | ||||||
| <td> |        | otherwise = [hamlet| | ||||||
|  <input.textinput size=15 name=#{amtvar} value=""> |           <td #addbtncell style="text-align:right;"> | ||||||
| |] |            <input type=hidden name=action value=add> | ||||||
|                      ,"eg: $6" |            <button type=submit .btn .btn-lg name=submit>add | ||||||
|                      ) |            $if length files' > 1 | ||||||
|        | otherwise = ("From account" :: String |             <br>to: ^{journalselect files'} | ||||||
|                      ,"eg: assets:bank:checking" :: String |          |] | ||||||
|                      ,nulltemplate |        where | ||||||
|                      ,"" :: String |         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 | ||||||
| @ -305,14 +311,16 @@ balanceReportAsHtml :: WebOpts -> ViewData -> BalanceReport -> HtmlUrl AppRoute | |||||||
| balanceReportAsHtml _ vd@VD{..} (items',total) = | balanceReportAsHtml _ vd@VD{..} (items',total) = | ||||||
|  [hamlet| |  [hamlet| | ||||||
|  <table.balancereport> |  <table.balancereport> | ||||||
|  |   <tr> | ||||||
|  |    <td>Account | ||||||
|  |    <td align=right>Balance | ||||||
|   $forall i <- items |   $forall i <- items | ||||||
|    ^{itemAsHtml vd i} |    ^{itemAsHtml vd i} | ||||||
|   <tr.totalrule> |   <tr.totalrule> | ||||||
|    <td colspan=3> |    <td colspan=2> | ||||||
|   <tr> |   <tr> | ||||||
|    <td> |    <td> | ||||||
|    <td.balance align=right>#{mixedAmountAsHtml total} |    <td.balance align=right>#{mixedAmountAsHtml total} | ||||||
|    <td> |  | ||||||
| |] | |] | ||||||
|  where |  where | ||||||
|    l = ledgerFromJournal Any j |    l = ledgerFromJournal Any j | ||||||
| @ -323,11 +331,11 @@ balanceReportAsHtml _ vd@VD{..} (items',total) = | |||||||
| <tr.item.#{inacctclass}> | <tr.item.#{inacctclass}> | ||||||
|  <td.account.#{depthclass}> |  <td.account.#{depthclass}> | ||||||
|   \#{indent} |   \#{indent} | ||||||
|   <a href="@?{acctquery}" title="Show transactions in this account, including subaccounts">#{adisplay} |    <a href="@?{acctquery}" title="Show transactions affecting this account and subaccounts">#{adisplay} | ||||||
|   <span.hoverlinks> |    <span.hoverlinks> | ||||||
|    $if hassubs |     $if hassubs | ||||||
|       |        | ||||||
|     <a href="@?{acctonlyquery}" title="Show transactions in this account, excluding subaccounts">only |      <a href="@?{acctonlyquery}" title="Show transactions affecting this account but not subaccounts">only | ||||||
| 
 | 
 | ||||||
|  <td.balance align=right>#{mixedAmountAsHtml abal} |  <td.balance align=right>#{mixedAmountAsHtml abal} | ||||||
| |] | |] | ||||||
| @ -352,164 +360,6 @@ accountOnlyQuery a = "inacctonly:" ++ quoteIfSpaced a -- (accountNameToAccountRe | |||||||
| accountUrl :: AppRoute -> AccountName -> (AppRoute, [(Text, Text)]) | accountUrl :: AppRoute -> AccountName -> (AppRoute, [(Text, Text)]) | ||||||
| accountUrl r a = (r, [("q", pack $ accountQuery a)]) | accountUrl r a = (r, [("q", pack $ accountQuery a)]) | ||||||
| 
 | 
 | ||||||
| -- | Render an "EntriesReport" as html for the journal entries view. |  | ||||||
| entriesReportAsHtml :: WebOpts -> ViewData -> EntriesReport -> HtmlUrl AppRoute |  | ||||||
| entriesReportAsHtml _ vd items = [hamlet| |  | ||||||
| <table.entriesreport> |  | ||||||
|  $forall i <- numbered items |  | ||||||
|   ^{itemAsHtml vd i} |  | ||||||
|  |] |  | ||||||
|  where |  | ||||||
|    itemAsHtml :: ViewData -> (Int, EntriesReportItem) -> HtmlUrl AppRoute |  | ||||||
|    itemAsHtml _ (n, t) = [hamlet| |  | ||||||
| <tr.item.#{evenodd}> |  | ||||||
|  <td.transaction> |  | ||||||
|   <pre>#{txn} |  | ||||||
|  |] |  | ||||||
|      where |  | ||||||
|        evenodd = if even n then "even" else "odd" :: String |  | ||||||
|        txn = trimnl $ showTransaction t where trimnl = reverse . dropWhile (=='\n') . reverse |  | ||||||
| 
 |  | ||||||
| -- | Render a "TransactionsReport" as html for the formatted journal view. |  | ||||||
| journalTransactionsReportAsHtml :: WebOpts -> ViewData -> TransactionsReport -> HtmlUrl AppRoute |  | ||||||
| journalTransactionsReportAsHtml _ vd (_,items) = [hamlet| |  | ||||||
| <table.transactionsreport> |  | ||||||
|  <tr.headings> |  | ||||||
|   <th.date style="text-align:left;">Date |  | ||||||
|   <th.description style="text-align:left;">Description |  | ||||||
|   <th.account style="text-align:left;">Accounts |  | ||||||
|   <th.amount style="text-align:right;">Amount |  | ||||||
|  $forall i <- numberTransactionsReportItems items |  | ||||||
|   ^{itemAsHtml vd i} |  | ||||||
|  |] |  | ||||||
|  where |  | ||||||
| -- .#{datetransition} |  | ||||||
|    itemAsHtml :: ViewData -> (Int, Bool, Bool, Bool, TransactionsReportItem) -> HtmlUrl AppRoute |  | ||||||
|    itemAsHtml VD{..} (n, _, _, _, (t, _, split, _, amt, _)) = [hamlet| |  | ||||||
| <tr.item.#{evenodd}.#{firstposting}> |  | ||||||
|  <td.date>#{date} |  | ||||||
|  <td.description colspan=2>#{elideRight 60 desc} |  | ||||||
|  <td.amount style="text-align:right;"> |  | ||||||
|   $if showamt |  | ||||||
|    \#{mixedAmountAsHtml amt} |  | ||||||
| $forall p' <- tpostings t |  | ||||||
|   <tr.item.#{evenodd}.posting> |  | ||||||
|    <td.date> |  | ||||||
|    <td.description> |  | ||||||
|    <td.account> #{elideRight 40 $ paccount p'} |  | ||||||
|    <td.amount style="text-align:right;">#{mixedAmountAsHtml $ pamount p'} |  | ||||||
| <tr> |  | ||||||
|  <td>  |  | ||||||
|  <td> |  | ||||||
|  <td> |  | ||||||
|  <td> |  | ||||||
| |] |  | ||||||
|      where |  | ||||||
|        evenodd = if even n then "even" else "odd" :: String |  | ||||||
|        -- datetransition | newm = "newmonth" |  | ||||||
|        --                | newd = "newday" |  | ||||||
|        --                | otherwise = "" :: String |  | ||||||
|        (firstposting, date, desc) = (False, show $ tdate t, tdescription t) |  | ||||||
|        -- acctquery = (here, [("q", pack $ accountQuery acct)]) |  | ||||||
|        showamt = not split || not (isZeroMixedAmount amt) |  | ||||||
| 
 |  | ||||||
| -- Generate html for an account register, including a balance chart and transaction list. |  | ||||||
| registerReportHtml :: WebOpts -> ViewData -> TransactionsReport -> HtmlUrl AppRoute |  | ||||||
| registerReportHtml opts vd r = [hamlet| |  | ||||||
|  ^{registerChartHtml $ map snd $ transactionsReportByCommodity r} |  | ||||||
|  ^{registerItemsHtml opts vd r} |  | ||||||
| |] |  | ||||||
| 
 |  | ||||||
| -- Generate html for a transaction list from an "TransactionsReport". |  | ||||||
| registerItemsHtml :: WebOpts -> ViewData -> TransactionsReport -> HtmlUrl AppRoute |  | ||||||
| registerItemsHtml _ vd (balancelabel,items) = [hamlet| |  | ||||||
| <table.registerreport> |  | ||||||
|  <tr.headings> |  | ||||||
|   <th.date style="text-align:left;">Date |  | ||||||
|   <th.description style="text-align:left;">Description |  | ||||||
|   <th.account style="text-align:left;">To/From Account(s) |  | ||||||
|     <!-- \ # |  | ||||||
|     <a#all-postings-toggle-link.togglelink href="#" title="Toggle all split postings">[+] --> |  | ||||||
|   $if inacct |  | ||||||
|    <th.amount style="text-align:right;">Amount |  | ||||||
|    <th.balance style="text-align:right;">#{balancelabel} |  | ||||||
| 
 |  | ||||||
|  $forall i <- numberTransactionsReportItems items |  | ||||||
|   ^{itemAsHtml vd i} |  | ||||||
| 
 |  | ||||||
|  |] |  | ||||||
|  where |  | ||||||
|    inacct = isJust $ inAccount $ qopts vd |  | ||||||
|    -- filtering = m /= Any |  | ||||||
|    itemAsHtml :: ViewData -> (Int, Bool, Bool, Bool, TransactionsReportItem) -> HtmlUrl AppRoute |  | ||||||
|    itemAsHtml VD{..} (n, newd, newm, _, (t, _, split, acct, amt, bal)) = [hamlet| |  | ||||||
| 
 |  | ||||||
| <tr.item.#{evenodd}.#{firstposting}.#{datetransition}> |  | ||||||
|  <td.date>#{date} |  | ||||||
|  <td.description title="#{show t}">#{elideRight 30 desc} |  | ||||||
|  <td.account title="#{show t}"> |  | ||||||
|   \#{elideRight 40 acct} |  | ||||||
|  $if inacct |  | ||||||
|   <td.amount style="text-align:right; white-space:nowrap;"> |  | ||||||
|    $if showamt |  | ||||||
|     \#{mixedAmountAsHtml amt} |  | ||||||
|   <td.balance style="text-align:right;">#{mixedAmountAsHtml bal} |  | ||||||
|  $else |  | ||||||
|   $forall p' <- tpostings t |  | ||||||
|    <tr.item.#{evenodd}.posting> |  | ||||||
|    <td.date> |  | ||||||
|    <td.description> |  | ||||||
|    <td.account> <a href="@?{accountUrl here $ paccount p'}" title="Show transactions in #{paccount p'}">#{elideRight 40 $ paccount p'} |  | ||||||
|     <td.amount style="text-align:right;">#{mixedAmountAsHtml $ pamount p'} |  | ||||||
|     <td.balance style="text-align:right;"> |  | ||||||
| 
 |  | ||||||
| |] |  | ||||||
|      where |  | ||||||
|        evenodd = if even n then "even" else "odd" :: String |  | ||||||
|        datetransition | newm = "newmonth" |  | ||||||
|                       | newd = "newday" |  | ||||||
|                       | otherwise = "" :: String |  | ||||||
|        (firstposting, date, desc) = (False, show $ tdate t, tdescription t) |  | ||||||
|        -- acctquery = (here, [("q", pack $ accountQuery acct)]) |  | ||||||
|        showamt = not split || not (isZeroMixedAmount amt) |  | ||||||
| 
 |  | ||||||
| -- | Generate javascript/html for a register balance line chart based on |  | ||||||
| -- the provided "TransactionsReportItem"s. |  | ||||||
|                -- registerChartHtml :: forall t (t1 :: * -> *) t2 t3 t4 t5. |  | ||||||
|                --                      Data.Foldable.Foldable t1 => |  | ||||||
|                --                      t1 (Transaction, t2, t3, t4, t5, MixedAmount) |  | ||||||
|                --                      -> t -> Text.Blaze.Internal.HtmlM () |  | ||||||
| registerChartHtml :: [[TransactionsReportItem]] -> HtmlUrl AppRoute |  | ||||||
| registerChartHtml itemss = |  | ||||||
|  -- have to make sure plot is not called when our container (maincontent) |  | ||||||
|  -- is hidden, eg with add form toggled |  | ||||||
|  [hamlet| |  | ||||||
| <div#register-chart style="width:600px;height:100px; margin-bottom:1em;"> |  | ||||||
| <script type=text/javascript> |  | ||||||
|  \$(document).ready(function() { |  | ||||||
|    /* render chart with flot, if visible */ |  | ||||||
|    var chartdiv = $('#register-chart'); |  | ||||||
|    if (chartdiv.is(':visible')) |  | ||||||
|      \$.plot(chartdiv, |  | ||||||
|              [ |  | ||||||
|               $forall items <- itemss |  | ||||||
|                [ |  | ||||||
|                 $forall i <- reverse items |  | ||||||
|                  [#{dayToJsTimestamp $ triDate i}, #{triSimpleBalance i}], |  | ||||||
|                 [] |  | ||||||
|                ], |  | ||||||
|               [] |  | ||||||
|              ], |  | ||||||
|              { |  | ||||||
|                xaxis: { |  | ||||||
|                 mode: "time", |  | ||||||
|                 timeformat: "%y/%m/%d" |  | ||||||
|                } |  | ||||||
|              } |  | ||||||
|              ); |  | ||||||
|   }); |  | ||||||
| |] |  | ||||||
| 
 |  | ||||||
| -- stringIfLongerThan :: Int -> String -> String | -- stringIfLongerThan :: Int -> String -> String | ||||||
| -- stringIfLongerThan n s = if length s > n then s else "" | -- stringIfLongerThan n s = if length s > n then s else "" | ||||||
| 
 | 
 | ||||||
|  | |||||||
| @ -33,8 +33,8 @@ getJournalEntriesR = do | |||||||
|   ^{sidecontent} |   ^{sidecontent} | ||||||
|  <div#main.journal> |  <div#main.journal> | ||||||
|   <div#maincontent> |   <div#maincontent> | ||||||
|    <h2#contenttitle>#{title} |  | ||||||
|    ^{searchform vd} |    ^{searchform vd} | ||||||
|  |    <h2#contenttitle>#{title} | ||||||
|    ^{maincontent} |    ^{maincontent} | ||||||
|   ^{addform staticRootUrl vd} |   ^{addform staticRootUrl vd} | ||||||
|   ^{editform vd} |   ^{editform vd} | ||||||
| @ -44,3 +44,21 @@ getJournalEntriesR = do | |||||||
| postJournalEntriesR :: Handler Html | postJournalEntriesR :: Handler Html | ||||||
| postJournalEntriesR = handlePost | postJournalEntriesR = handlePost | ||||||
| 
 | 
 | ||||||
|  | -- | Render an "EntriesReport" as html for the journal entries view. | ||||||
|  | entriesReportAsHtml :: WebOpts -> ViewData -> EntriesReport -> HtmlUrl AppRoute | ||||||
|  | entriesReportAsHtml _ vd items = [hamlet| | ||||||
|  | <table.entriesreport> | ||||||
|  |  $forall i <- numbered items | ||||||
|  |   ^{itemAsHtml vd i} | ||||||
|  |  |] | ||||||
|  |  where | ||||||
|  |    itemAsHtml :: ViewData -> (Int, EntriesReportItem) -> HtmlUrl AppRoute | ||||||
|  |    itemAsHtml _ (n, t) = [hamlet| | ||||||
|  | <tr.item.#{evenodd}> | ||||||
|  |  <td.transaction> | ||||||
|  |   <pre>#{txn} | ||||||
|  |  |] | ||||||
|  |      where | ||||||
|  |        evenodd = if even n then "even" else "odd" :: String | ||||||
|  |        txn = trimnl $ showTransaction t where trimnl = reverse . dropWhile (=='\n') . reverse | ||||||
|  | 
 | ||||||
|  | |||||||
| @ -8,8 +8,10 @@ import Handler.Common | |||||||
| import Handler.Post | import Handler.Post | ||||||
| import Handler.Utils | import Handler.Utils | ||||||
| 
 | 
 | ||||||
|  | import Hledger.Data | ||||||
| import Hledger.Query | import Hledger.Query | ||||||
| import Hledger.Reports | import Hledger.Reports | ||||||
|  | import Hledger.Utils | ||||||
| import Hledger.Cli.Options | import Hledger.Cli.Options | ||||||
| import Hledger.Web.Options | import Hledger.Web.Options | ||||||
| 
 | 
 | ||||||
| @ -18,8 +20,7 @@ getJournalR :: Handler Html | |||||||
| getJournalR = do | getJournalR = do | ||||||
|   vd@VD{..} <- getViewData |   vd@VD{..} <- getViewData | ||||||
|   staticRootUrl <- (staticRoot . settings) <$> getYesod |   staticRootUrl <- (staticRoot . settings) <$> getYesod | ||||||
|   let sidecontent = sidebar vd |   let -- XXX like registerReportAsHtml | ||||||
|       -- XXX like registerReportAsHtml |  | ||||||
|       inacct = inAccount qopts |       inacct = inAccount qopts | ||||||
|       -- injournal = isNothing inacct |       -- injournal = isNothing inacct | ||||||
|       filtering = m /= Any |       filtering = m /= Any | ||||||
| @ -27,27 +28,66 @@ getJournalR = do | |||||||
|       title = case inacct of |       title = case inacct of | ||||||
|                 Nothing       -> "General Journal"++s2 |                 Nothing       -> "General Journal"++s2 | ||||||
|                 Just (a,inclsubs) -> "Transactions in "++a++s1++s2 |                 Just (a,inclsubs) -> "Transactions in "++a++s1++s2 | ||||||
|                                       where s1 = if inclsubs then " including subs" else " excluding subs" |                                       where s1 = if inclsubs then "" else " (excluding subaccounts)" | ||||||
|                 where |                 where | ||||||
|                   s2 = if filtering then ", filtered" else "" |                   s2 = if filtering then ", filtered" else "" | ||||||
|       maincontent = journalTransactionsReportAsHtml opts vd $ journalTransactionsReport (reportopts_ $ cliopts_ opts) j m |       maincontent = journalTransactionsReportAsHtml opts vd $ journalTransactionsReport (reportopts_ $ cliopts_ opts) j m | ||||||
|   defaultLayout $ do |   hledgerLayout vd "journal" [hamlet| | ||||||
|       setTitle "hledger-web journal" |        <h2#contenttitle>#{title} | ||||||
|       toWidget [hamlet| |        <!-- p>Journal entries record movements of commodities between accounts. --> | ||||||
| ^{topbar vd} |        <a#addformlink role="button" style="cursor:pointer;" onclick="addformToggle()" title="Add a new transaction to the journal" style="margin-top:1em;">Add transaction | ||||||
| <div#content> |        ^{addform staticRootUrl vd} | ||||||
|  <div#sidebar> |        <p> | ||||||
|   ^{sidecontent} |        ^{maincontent} | ||||||
|  <div#main.register> |      |] | ||||||
|   <div#maincontent> |  | ||||||
|    <h2#contenttitle>#{title} |  | ||||||
|    ^{searchform vd} |  | ||||||
|    ^{maincontent} |  | ||||||
|   ^{addform staticRootUrl vd} |  | ||||||
|   ^{editform vd} |  | ||||||
|   ^{importform} |  | ||||||
| |] |  | ||||||
| 
 | 
 | ||||||
| postJournalR :: Handler Html | postJournalR :: Handler Html | ||||||
| postJournalR = handlePost | postJournalR = handlePost | ||||||
| 
 | 
 | ||||||
|  | -- | Render a "TransactionsReport" as html for the formatted journal view. | ||||||
|  | journalTransactionsReportAsHtml :: WebOpts -> ViewData -> TransactionsReport -> HtmlUrl AppRoute | ||||||
|  | journalTransactionsReportAsHtml _ vd (_,items) = [hamlet| | ||||||
|  | <table.transactionsreport> | ||||||
|  |  <tr.headings> | ||||||
|  |   <th.date style="text-align:left;"> | ||||||
|  |    Date | ||||||
|  |    <span .glyphicon .glyphicon-chevron-up> | ||||||
|  |   <th.description style="text-align:left;">Description | ||||||
|  |   <th.account style="text-align:left;">Account | ||||||
|  |   <th.amount style="text-align:right;">Amount | ||||||
|  |  $forall i <- numberTransactionsReportItems items | ||||||
|  |   ^{itemAsHtml vd i} | ||||||
|  |  |] | ||||||
|  |  where | ||||||
|  | -- .#{datetransition} | ||||||
|  |    itemAsHtml :: ViewData -> (Int, Bool, Bool, Bool, TransactionsReportItem) -> HtmlUrl AppRoute | ||||||
|  |    itemAsHtml VD{..} (n, _, _, _, (t, _, split, _, amt, _)) = [hamlet| | ||||||
|  | <tr ##{date} .item.#{evenodd}.#{firstposting} style="vertical-align:top;" title="#{show t}"> | ||||||
|  |  <td.date>#{date} | ||||||
|  |  <td.description colspan=2>#{elideRight 60 desc} | ||||||
|  |  <td.amount style="text-align:right;"> | ||||||
|  |   $if showamt | ||||||
|  |    \#{mixedAmountAsHtml amt} | ||||||
|  | $forall p' <- tpostings t | ||||||
|  |  <tr .item.#{evenodd}.posting title="#{show t}"> | ||||||
|  |   <td.date> | ||||||
|  |   <td.description> | ||||||
|  |   <td.account> | ||||||
|  |      | ||||||
|  |    <a href="/register?q=inacct:'#{paccount p'}'##{date}">#{elideRight 40 $ paccount p'} | ||||||
|  |   <td.amount style="text-align:right;">#{mixedAmountAsHtml $ pamount p'} | ||||||
|  | <tr.#{evenodd}> | ||||||
|  |  <td>  | ||||||
|  |  <td> | ||||||
|  |  <td> | ||||||
|  |  <td> | ||||||
|  | |] | ||||||
|  |      where | ||||||
|  |        evenodd = if even n then "even" else "odd" :: String | ||||||
|  |        -- datetransition | newm = "newmonth" | ||||||
|  |        --                | newd = "newday" | ||||||
|  |        --                | otherwise = "" :: String | ||||||
|  |        (firstposting, date, desc) = (False, show $ tdate t, tdescription t) | ||||||
|  |        -- acctquery = (here, [("q", pack $ accountQuery acct)]) | ||||||
|  |        showamt = not split || not (isZeroMixedAmount amt) | ||||||
|  | 
 | ||||||
|  | |||||||
| @ -87,7 +87,7 @@ handleAdd = do | |||||||
|     -- setMessage $ toHtml $ (printf "Added transaction:\n%s" (show t') :: String) |     -- setMessage $ toHtml $ (printf "Added transaction:\n%s" (show t') :: String) | ||||||
|     setMessage [shamlet|<span>Added transaction:<small><pre>#{chomp $ show t'}</pre></small>|] |     setMessage [shamlet|<span>Added transaction:<small><pre>#{chomp $ show t'}</pre></small>|] | ||||||
| 
 | 
 | ||||||
|   redirect (RegisterR, [("add","1")]) |   redirect (JournalR, [("add","1")]) | ||||||
| 
 | 
 | ||||||
| -- | Handle a post from the journal edit form. | -- | Handle a post from the journal edit form. | ||||||
| handleEdit :: Handler Html | handleEdit :: Handler Html | ||||||
|  | |||||||
| @ -10,8 +10,10 @@ import Handler.Common | |||||||
| import Handler.Post | import Handler.Post | ||||||
| import Handler.Utils | import Handler.Utils | ||||||
| 
 | 
 | ||||||
|  | import Hledger.Data | ||||||
| import Hledger.Query | import Hledger.Query | ||||||
| import Hledger.Reports | import Hledger.Reports | ||||||
|  | import Hledger.Utils | ||||||
| import Hledger.Cli.Options | import Hledger.Cli.Options | ||||||
| import Hledger.Web.Options | import Hledger.Web.Options | ||||||
| 
 | 
 | ||||||
| @ -19,32 +21,116 @@ import Hledger.Web.Options | |||||||
| getRegisterR :: Handler Html | getRegisterR :: Handler Html | ||||||
| getRegisterR = do | getRegisterR = do | ||||||
|   vd@VD{..} <- getViewData |   vd@VD{..} <- getViewData | ||||||
|   staticRootUrl <- (staticRoot . settings) <$> getYesod |   -- staticRootUrl <- (staticRoot . settings) <$> getYesod | ||||||
|   let sidecontent = sidebar vd |   let -- injournal = isNothing inacct | ||||||
|       -- injournal = isNothing inacct |  | ||||||
|       filtering = m /= Any |       filtering = m /= Any | ||||||
|       title = "Transactions in "++a++s1++s2 |       -- title = "Transactions in "++a++s1++s2 | ||||||
|  |       title = a++s1++s2 | ||||||
|                where |                where | ||||||
|                  (a,inclsubs) = fromMaybe ("all accounts",False) $ inAccount qopts |                  (a,inclsubs) = fromMaybe ("all accounts",True) $ inAccount qopts | ||||||
|                  s1 = if inclsubs then " including subs" else " excluding subs" |                  s1 = if inclsubs then "" else " (excluding subaccounts)" | ||||||
|                  s2 = if filtering then ", filtered" else "" |                  s2 = if filtering then ", filtered" else "" | ||||||
|       maincontent = registerReportHtml opts vd $ accountTransactionsReport (reportopts_ $ cliopts_ opts) j m $ fromMaybe Any $ inAccountQuery qopts |       maincontent = registerReportHtml opts vd $ accountTransactionsReport (reportopts_ $ cliopts_ opts) j m $ fromMaybe Any $ inAccountQuery qopts | ||||||
|   defaultLayout $ do |   hledgerLayout vd "register" [hamlet| | ||||||
|       setTitle "hledger-web register" |        <h2#contenttitle>#{title} | ||||||
|       toWidget [hamlet| |        <!-- p>Transactions affecting this account, with running balance. --> | ||||||
| ^{topbar vd} |        ^{maincontent} | ||||||
| <div#content> |      |] | ||||||
|  <div#sidebar> |  | ||||||
|   ^{sidecontent} |  | ||||||
|  <div#main.register> |  | ||||||
|   <div#maincontent> |  | ||||||
|    <h2#contenttitle>#{title} |  | ||||||
|    ^{searchform vd} |  | ||||||
|    ^{maincontent} |  | ||||||
|   ^{addform staticRootUrl vd} |  | ||||||
|   ^{editform vd} |  | ||||||
|   ^{importform} |  | ||||||
| |] |  | ||||||
| 
 | 
 | ||||||
| postRegisterR :: Handler Html | postRegisterR :: Handler Html | ||||||
| postRegisterR = handlePost | postRegisterR = handlePost | ||||||
|  | 
 | ||||||
|  | -- Generate html for an account register, including a balance chart and transaction list. | ||||||
|  | registerReportHtml :: WebOpts -> ViewData -> TransactionsReport -> HtmlUrl AppRoute | ||||||
|  | registerReportHtml opts vd r = [hamlet| | ||||||
|  |  ^{registerChartHtml $ map snd $ transactionsReportByCommodity r} | ||||||
|  |  ^{registerItemsHtml opts vd r} | ||||||
|  | |] | ||||||
|  | 
 | ||||||
|  | -- Generate html for a transaction list from an "TransactionsReport". | ||||||
|  | registerItemsHtml :: WebOpts -> ViewData -> TransactionsReport -> HtmlUrl AppRoute | ||||||
|  | registerItemsHtml _ vd (balancelabel,items) = [hamlet| | ||||||
|  | <table.registerreport> | ||||||
|  |  <tr.headings> | ||||||
|  |   <th.date style="text-align:left;"> | ||||||
|  |    Date | ||||||
|  |    <span .glyphicon .glyphicon-chevron-up> | ||||||
|  |   <th.description style="text-align:left;">Description | ||||||
|  |   <th.account style="text-align:left;">To/From Account | ||||||
|  |   <th.amount style="text-align:right;">Amount Out/In | ||||||
|  |   <th.balance style="text-align:right;">#{balancelabel'} | ||||||
|  |  $forall i <- numberTransactionsReportItems items | ||||||
|  |   ^{itemAsHtml vd i} | ||||||
|  |  |] | ||||||
|  |  where | ||||||
|  |    insomeacct = isJust $ inAccount $ qopts vd | ||||||
|  |    balancelabel' = if insomeacct then balancelabel else "Total" | ||||||
|  | 
 | ||||||
|  |    -- filtering = m /= Any | ||||||
|  |    itemAsHtml :: ViewData -> (Int, Bool, Bool, Bool, TransactionsReportItem) -> HtmlUrl AppRoute | ||||||
|  |    itemAsHtml VD{..} (n, newd, newm, _, (t, _, split, acct, amt, bal)) = [hamlet| | ||||||
|  | 
 | ||||||
|  | <tr ##{date} .item.#{evenodd}.#{firstposting}.#{datetransition} title="#{show t}" style="vertical-align:top;"> | ||||||
|  |  <td.date><a href="/journal##{date}">#{date} | ||||||
|  |  <td.description title="#{show t}">#{elideRight 30 desc} | ||||||
|  |  <td.account>#{elideRight 40 acct} | ||||||
|  |  <td.amount style="text-align:right; white-space:nowrap;"> | ||||||
|  |   $if showamt | ||||||
|  |    \#{mixedAmountAsHtml amt} | ||||||
|  |  <td.balance style="text-align:right;">#{mixedAmountAsHtml bal} | ||||||
|  | |] | ||||||
|  |  -- $else | ||||||
|  |  --  $forall p' <- tpostings t | ||||||
|  |  --   <tr.item.#{evenodd}.posting> | ||||||
|  |  --   <td.date> | ||||||
|  |  --   <td.description> | ||||||
|  |  --   <td.account> <a href="@?{accountUrl here $ paccount p'}" title="Show transactions in #{paccount p'}">#{elideRight 40 $ paccount p'} | ||||||
|  |  --    <td.amount style="text-align:right;">#{mixedAmountAsHtml $ pamount p'} | ||||||
|  |  --    <td.balance style="text-align:right;"> | ||||||
|  | 
 | ||||||
|  |      where | ||||||
|  |        evenodd = if even n then "even" else "odd" :: String | ||||||
|  |        datetransition | newm = "newmonth" | ||||||
|  |                       | newd = "newday" | ||||||
|  |                       | otherwise = "" :: String | ||||||
|  |        (firstposting, date, desc) = (False, show $ tdate t, tdescription t) | ||||||
|  |        -- acctquery = (here, [("q", pack $ accountQuery acct)]) | ||||||
|  |        showamt = not split || not (isZeroMixedAmount amt) | ||||||
|  | 
 | ||||||
|  | -- | Generate javascript/html for a register balance line chart based on | ||||||
|  | -- the provided "TransactionsReportItem"s. | ||||||
|  |                -- registerChartHtml :: forall t (t1 :: * -> *) t2 t3 t4 t5. | ||||||
|  |                --                      Data.Foldable.Foldable t1 => | ||||||
|  |                --                      t1 (Transaction, t2, t3, t4, t5, MixedAmount) | ||||||
|  |                --                      -> t -> Text.Blaze.Internal.HtmlM () | ||||||
|  | registerChartHtml :: [[TransactionsReportItem]] -> HtmlUrl AppRoute | ||||||
|  | registerChartHtml itemss = | ||||||
|  |  -- have to make sure plot is not called when our container (maincontent) | ||||||
|  |  -- is hidden, eg with add form toggled | ||||||
|  |  [hamlet| | ||||||
|  | <div#register-chart style="width:600px;height:100px; margin-bottom:1em;"> | ||||||
|  | <script type=text/javascript> | ||||||
|  |  \$(document).ready(function() { | ||||||
|  |    /* render chart with flot, if visible */ | ||||||
|  |    var chartdiv = $('#register-chart'); | ||||||
|  |    if (chartdiv.is(':visible')) | ||||||
|  |      \$.plot(chartdiv, | ||||||
|  |              [ | ||||||
|  |               $forall items <- itemss | ||||||
|  |                [ | ||||||
|  |                 $forall i <- reverse items | ||||||
|  |                  [#{dayToJsTimestamp $ triDate i}, #{triSimpleBalance i}], | ||||||
|  |                 [] | ||||||
|  |                ], | ||||||
|  |               [] | ||||||
|  |              ], | ||||||
|  |              { | ||||||
|  |                xaxis: { | ||||||
|  |                 mode: "time", | ||||||
|  |                 timeformat: "%y/%m/%d" | ||||||
|  |                } | ||||||
|  |              } | ||||||
|  |              ); | ||||||
|  |   }); | ||||||
|  | |] | ||||||
|  | 
 | ||||||
|  | |||||||
| @ -34,6 +34,7 @@ data ViewData = VD { | |||||||
|     ,am           :: Query    -- ^ a query parsed from the accounts sidebar query expr ("a" 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 |     ,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 |     ,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. | -- | Make a default ViewData, using day 0 as today's date. | ||||||
| @ -57,6 +58,7 @@ viewdataWithDateAndParams d q a p = | |||||||
|           ,am           = acctsmatcher |           ,am           = acctsmatcher | ||||||
|           ,aopts        = acctsopts |           ,aopts        = acctsopts | ||||||
|           ,showpostings = p == "1" |           ,showpostings = p == "1" | ||||||
|  |           ,showsidebar  = False | ||||||
|           } |           } | ||||||
| 
 | 
 | ||||||
| -- | Gather data used by handlers and templates in the current request. | -- | Gather data used by handlers and templates in the current request. | ||||||
| @ -71,12 +73,15 @@ getViewData = do | |||||||
|   q          <- getParameterOrNull "q" |   q          <- getParameterOrNull "q" | ||||||
|   a          <- getParameterOrNull "a" |   a          <- getParameterOrNull "a" | ||||||
|   p          <- getParameterOrNull "p" |   p          <- getParameterOrNull "p" | ||||||
|  |   cookies <- reqCookies <$> getRequest | ||||||
|  |   let showsidebar = maybe False (=="1") $ lookup "showsidebar" cookies | ||||||
|   return (viewdataWithDateAndParams today q a p){ |   return (viewdataWithDateAndParams today q a p){ | ||||||
|                opts=opts |                opts=opts | ||||||
|               ,msg=msg |               ,msg=msg | ||||||
|               ,here=here |               ,here=here | ||||||
|               ,today=today |               ,today=today | ||||||
|               ,j=j |               ,j=j | ||||||
|  |               ,showsidebar=showsidebar | ||||||
|               } |               } | ||||||
|     where |     where | ||||||
|       -- | Update our copy of the journal if the file changed. If there is an |       -- | Update our copy of the journal if the file changed. If there is an | ||||||
|  | |||||||
| @ -1,14 +1,12 @@ | |||||||
| /static          StaticR         Static getStatic |  | ||||||
| /favicon.ico     FaviconR        GET | /favicon.ico     FaviconR        GET | ||||||
| /robots.txt      RobotsR         GET | /robots.txt      RobotsR         GET | ||||||
| 
 | /static          StaticR         Static getStatic | ||||||
| /                RootR           GET | /                RootR           GET | ||||||
| 
 |  | ||||||
| /journal         JournalR        GET POST | /journal         JournalR        GET POST | ||||||
| /journal/entries JournalEntriesR GET POST |  | ||||||
| /journal/edit    JournalEditR    GET POST |  | ||||||
| 
 |  | ||||||
| /register        RegisterR       GET POST | /register        RegisterR       GET POST | ||||||
| 
 | /sidebar         SidebarR        GET | ||||||
|  | -- /journal/entries JournalEntriesR GET POST | ||||||
|  | -- /journal/edit    JournalEditR    GET POST | ||||||
|  | -- | ||||||
| -- /accounts        AccountsR       GET | -- /accounts        AccountsR       GET | ||||||
| -- /api/accounts    AccountsJsonR   GET | -- /api/accounts    AccountsJsonR   GET | ||||||
|  | |||||||
| @ -114,6 +114,7 @@ library | |||||||
|                      Handler.Post |                      Handler.Post | ||||||
|                      Handler.RegisterR |                      Handler.RegisterR | ||||||
|                      Handler.RootR |                      Handler.RootR | ||||||
|  |                      Handler.SidebarR | ||||||
|                      Handler.Utils |                      Handler.Utils | ||||||
|     other-modules: |     other-modules: | ||||||
|                      Hledger.Web |                      Hledger.Web | ||||||
| @ -215,6 +216,7 @@ executable         hledger-web | |||||||
|                      Handler.Post |                      Handler.Post | ||||||
|                      Handler.RegisterR |                      Handler.RegisterR | ||||||
|                      Handler.RootR |                      Handler.RootR | ||||||
|  |                      Handler.SidebarR | ||||||
|                      Handler.Utils |                      Handler.Utils | ||||||
|                      Hledger.Web |                      Hledger.Web | ||||||
|                      Hledger.Web.Main |                      Hledger.Web.Main | ||||||
|  | |||||||
| @ -6,10 +6,12 @@ | |||||||
| /* green */ | /* green */ | ||||||
| body                                                                 { background-color:white; color:black; } | body                                                                 { background-color:white; color:black; } | ||||||
| .registerreport .odd                                                 { background-color:#ded; } | .registerreport .odd                                                 { background-color:#ded; } | ||||||
| .transactionsreport .odd                                             { background-color:#eee; } | /* .transactionsreport .odd                                             { background-color:#eee; } */ | ||||||
| .filtering                                                           { background-color:#ded; } | .filtering                                                           { background-color:#e0e0e0; } | ||||||
| /* #main                                                                { border-color:#ded; } see below */ | a:link, a:visited { color:#00e; } | ||||||
| /* .journalreport td                                                    { border-color:thin solid #ded; } see below */ | /* a:link:hover, a:visited:hover { color:red; } */ | ||||||
|  | /* #main                                                                { border-color:#e0e0e0; } see below */ | ||||||
|  | /* .journalreport td                                                    { border-color:thin solid #e0e0e0; } see below */ | ||||||
| 
 | 
 | ||||||
| /* white */ | /* white */ | ||||||
| /* body                                                                 { background-color:#fff; } */ | /* body                                                                 { background-color:#fff; } */ | ||||||
| @ -19,28 +21,32 @@ body                                                                 { backgroun | |||||||
| /* .journalreport td                                                    { border-color:thin solid #eee; } see below */ | /* .journalreport td                                                    { border-color:thin solid #eee; } see below */ | ||||||
| 
 | 
 | ||||||
| #message                                                             { color:red; background-color:#fee; } | #message                                                             { color:red; background-color:#fee; } | ||||||
| #addform input.textinput, #addform .dhx_combo_input, .dhx_combo_list { background-color:#eee; } | /* #addform input.textinput, #addform .dhx_combo_input, .dhx_combo_list { /\*background-color:#eee;*\/ } */ | ||||||
| #editform textarea                                                   { background-color:#eee; } | #editform textarea                                                   { background-color:#eee; } | ||||||
| .negative                                                            { color:#800; } | .negative                                                            { color:#800; } | ||||||
| .help                                                                {  } | .help                                                                {  } | ||||||
| 
 | 
 | ||||||
| #sidebar .hoverlinks { visibility:hidden; } | #sidebar .hoverlinks { visibility:hidden; } | ||||||
| #sidebar .mouseover { background-color:rgba(208,208,208,0.5); } | /* #sidebar .mouseover { background-color:rgba(208,208,208,0.5); } */ | ||||||
| #sidebar .mouseover .hoverlinks { visibility:visible; } | #sidebar .mouseover .hoverlinks { visibility:visible; } | ||||||
| 
 | 
 | ||||||
| #sidebar .balancereport .hoverlinks { margin-left:0em; font-weight:normal; /*font-size:smaller;*/ display:inline-block; text-align:right; } | #sidebar .balancereport .hoverlinks { margin-left:0em; font-weight:normal; /*font-size:smaller;*/ display:inline-block; text-align:right; } | ||||||
| #sidebar .balancereport .hoverlinks a { margin-left:0.5em; } | #sidebar .balancereport .hoverlinks a { margin-left:0.5em; } | ||||||
| #sidebar .notinacct, .notinacct :link, .notinacct :visited { color:#888; } | /* #sidebar .notinacct, .notinacct :link, .notinacct :visited { color:#888; } */ | ||||||
| #sidebar .notinacct .negative { color:#b77; } | #sidebar .notinacct .negative { color:#b77; } | ||||||
| #sidebar .balancereport .inacct                                               { /*background-color:#ddd;*/ font-weight:bold; } | #sidebar .balancereport .inacct { font-weight:bold; } | ||||||
|  | /* #sidebar .balancereport .inacct { background-color:#e0e0e0; } */ | ||||||
| #sidebar .balancereport .numpostings                                          { padding-left:1em; color:#aaa; } | #sidebar .balancereport .numpostings                                          { padding-left:1em; color:#aaa; } | ||||||
|  | #sidebar .current { font-weight:bold; } | ||||||
| 
 | 
 | ||||||
| /*------------------------------------------------------------------------------------------*/ | /*------------------------------------------------------------------------------------------*/ | ||||||
| /* 2. font families & sizes */ | /* 2. font families & sizes */ | ||||||
| /* overspecified for cross-browser robustness */ | /* overspecified for cross-browser robustness */ | ||||||
|  | body { font-size:16px; } | ||||||
|  | /* | ||||||
| body                                               { font-family:helvetica,arial,sans-serif; } | body                                               { font-family:helvetica,arial,sans-serif; } | ||||||
| pre                                                { font-family:courier,"courier new",monospace; } | pre                                                { font-family:courier,"courier new",monospace; } | ||||||
| input.textinput, .dhx_combo_input, .dhx_combo_list { font-size:small; } | .dhx_combo_input, .dhx_combo_list { font-size:small; } | ||||||
| #editform textarea                                 { font-family:courier,"courier new",monospace; font-size:small; } | #editform textarea                                 { font-family:courier,"courier new",monospace; font-size:small; } | ||||||
| .nav2                                              { font-size:small; } | .nav2                                              { font-size:small; } | ||||||
| #searchform                                        { font-size:small; } | #searchform                                        { font-size:small; } | ||||||
| @ -55,15 +61,17 @@ input.textinput, .dhx_combo_input, .dhx_combo_list { font-size:small; } | |||||||
| .balancereport                                     { font-size:small; } | .balancereport                                     { font-size:small; } | ||||||
| .registerreport                                    { font-size:small; } | .registerreport                                    { font-size:small; } | ||||||
| .showall                                           { font-size:small; } | .showall                                           { font-size:small; } | ||||||
|  | */ | ||||||
| /* #addformlink                                    { font-size:small; } */ | /* #addformlink                                    { font-size:small; } */ | ||||||
| /* #editformlink                                   { font-size:small; } */ | /* #editformlink                                   { font-size:small; } */ | ||||||
|  | /* | ||||||
| #contenttitle                                    { font-size:1.2em; } | #contenttitle                                    { font-size:1.2em; } | ||||||
|  | */ | ||||||
| 
 | 
 | ||||||
| /*------------------------------------------------------------------------------------------*/ | /*------------------------------------------------------------------------------------------*/ | ||||||
| /* 3. layout */ | /* 3. layout */ | ||||||
| 
 | 
 | ||||||
| body                        { margin:0; } | body                        { margin:0; } | ||||||
| #content                    { padding:1em 0 0 0.5em; } |  | ||||||
| 
 | 
 | ||||||
| 
 | 
 | ||||||
| #topbar                     { padding:2px; } | #topbar                     { padding:2px; } | ||||||
| @ -80,7 +88,18 @@ body                        { margin:0; } | |||||||
| #outermain { overflow:auto; } | #outermain { overflow:auto; } | ||||||
| #main { overflow:auto; padding-left:1em; } | #main { overflow:auto; padding-left:1em; } | ||||||
| 
 | 
 | ||||||
| #sidebar { float:left; padding-right:1em; border-right:thin solid #ded; margin-bottom:5em; } | #sidebar { | ||||||
|  |   float:left; | ||||||
|  |   padding-right:1em;  | ||||||
|  |   border-right:thin solid #e0e0e0; | ||||||
|  |   margin-bottom:5em; | ||||||
|  | } | ||||||
|  | /* #sidebar.affix { */ | ||||||
|  | /*     position: fixed; */ | ||||||
|  | /*     top: 20px; */ | ||||||
|  | /* } */ | ||||||
|  | 
 | ||||||
|  | .balancereport .item { border-top:thin solid #e0e0e0; } | ||||||
| 
 | 
 | ||||||
| #navlinks                   { margin-bottom:1em; } | #navlinks                   { margin-bottom:1em; } | ||||||
| .navlink                    { } | .navlink                    { } | ||||||
| @ -130,160 +149,114 @@ table.registerreport tr.posting { font-size:smaller; } | |||||||
| table.registerreport tr.posting .account  { padding-left:1.5em; } | table.registerreport tr.posting .account  { padding-left:1.5em; } | ||||||
| table.registerreport tr.posting .amount  { padding-right:0.5em; } | table.registerreport tr.posting .amount  { padding-right:0.5em; } | ||||||
| tr.firstposting td          { } | tr.firstposting td          { } | ||||||
| tr.newday td                { border-top: 1px solid #797; } | /* tr.newday td                { border-top: 1px solid #797; } */ | ||||||
| /* tr.newday .date             { font-weight:bold; } */ | /* tr.newday .date             { font-weight:bold; } */ | ||||||
| tr.newmonth td              { border-top: 2px solid #464; } | /* tr.newmonth td              { border-top: 2px solid #464; } */ | ||||||
| /* tr.newyear td               { border-top: 3px solid black; } */ | /* tr.newyear td               { border-top: 3px solid black; } */ | ||||||
| #accountsheading            { white-space:nowrap; } | #accountsheading            { white-space:nowrap; } | ||||||
| 
 | 
 | ||||||
| 
 | 
 | ||||||
| #addform input.textinput, #addform .dhx_combo_input, .dhx_combo_list   { padding:4px; } | #addform { | ||||||
| #addform table              { } |   /* margin:0 0 2em; */ | ||||||
| #addform #addbuttonrow      { text-align:right; } |   /* padding:.5em 0; */ | ||||||
|  |   /* border-top:thin solid #e0e0e0; */ | ||||||
|  |   /* border-bottom:thin solid #e0e0e0; */ | ||||||
|  | } | ||||||
|  | #addform tr { | ||||||
|  |   vertical-align:top; | ||||||
|  | } | ||||||
|  | /* #addform input.textinput, #addform .dhx_combo_input, .dhx_combo_list   { padding:4px; } */ | ||||||
|  | /* #addform table              { } */ | ||||||
|  | /* #addform #addbuttonrow      { text-align:right; } */ | ||||||
| /* #editform                   { width:95%; } */ | /* #editform                   { width:95%; } */ | ||||||
| #editform textarea          { width:100%; padding:4px; } | #editform textarea          { width:100%; padding:4px; } | ||||||
| #searchform table           { border-spacing:0; padding-left:0em; } | /* #searchform table           { border-spacing:0; padding-left:0em; } */ | ||||||
| 
 | 
 | ||||||
|  | ::-moz-placeholder { | ||||||
|  |   font-style:italic; | ||||||
|  | } | ||||||
|  | :-moz-placeholder { | ||||||
|  |   font-style:italic; | ||||||
|  | } | ||||||
|  | ::-webkit-input-placeholder { | ||||||
|  |   font-style:italic; | ||||||
|  | } | ||||||
|  |  :-ms-input-placeholder { | ||||||
|  |   font-style:italic; | ||||||
|  | } | ||||||
| 
 | 
 | ||||||
| /*------------------------------------------------------------------------------------------*/ | /*------------------------------------------------------------------------------------------*/ | ||||||
| /* 4. dhtmlx.com auto-completing combo box styles */ | /* 4. typeahead styles */ | ||||||
| 
 | 
 | ||||||
| .dhx_combo_input{ | /* | ||||||
| /* color:#333333; */ | .typeahead, | ||||||
| /* font-family: Arial; */ | .tt-query, | ||||||
| /* font-size: 9pt; */ | .tt-hint { | ||||||
| /* border:0px; */ |   width: 396px; | ||||||
| /* padding:2px 2px 2px 2px; */ |   height: 30px; | ||||||
| /* position:absolute; */ |   padding: 8px 12px; | ||||||
| /* top:0px; */ |   font-size: 24px; | ||||||
|  |   line-height: 30px; | ||||||
|  |   border: 2px solid #ccc; | ||||||
|  |   -webkit-border-radius: 8px; | ||||||
|  |      -moz-border-radius: 8px; | ||||||
|  |           border-radius: 8px; | ||||||
|  |   outline: none; | ||||||
| } | } | ||||||
| 
 | 
 | ||||||
| /* table {border:thin solid red} */ | .typeahead { | ||||||
| /* div {border:thin solid yellow} */ |   background-color: #fff; | ||||||
| 
 |  | ||||||
| .dhx_combo_box{ |  | ||||||
|     position:relative; |  | ||||||
|     display:inline-block; |  | ||||||
|     /* text-align:left; */ |  | ||||||
|     /* height:20px; */ |  | ||||||
|     /* _height:22px; */ |  | ||||||
|     /* overflow:hidden; */ |  | ||||||
|     /* background-color: white; */ |  | ||||||
| } | } | ||||||
| 
 | 
 | ||||||
| .dhx_combo_list{ | .typeahead:focus { | ||||||
|     position:absolute; |   border: 2px solid #0097cf; | ||||||
|     z-index:230; |  | ||||||
|     overflow-y:auto; |  | ||||||
|     overflow-x:hidden; |  | ||||||
|     white-space:nowrap; |  | ||||||
|     border:1px solid black; |  | ||||||
|     height:50%; |  | ||||||
|     /* background-color: white; */ |  | ||||||
| } | } | ||||||
| 
 | 
 | ||||||
| .dhx_combo_list div{ | .tt-query { | ||||||
|     cursor:default; |   -webkit-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075); | ||||||
|     padding:2px 2px 2px 2px; |      -moz-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075); | ||||||
|  |           box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075); | ||||||
| } | } | ||||||
| 
 | 
 | ||||||
| .dhx_selected_option{ | */ | ||||||
|     background-color:navy; | .tt-hint { | ||||||
|     color:white; |   color: #bbb; | ||||||
| } | } | ||||||
| 
 | 
 | ||||||
| .dhx_combo_img{ | .tt-dropdown-menu { | ||||||
|     /* display:none; */ |   padding: 8px 0; | ||||||
|     width:18px; |   background-color: #fff; | ||||||
|     height:20px; |   border: 1px solid #ccc; | ||||||
|     position:absolute; |   border: 1px solid rgba(0, 0, 0, 0.2); | ||||||
|     top:12px; |   -webkit-border-radius: 8px; | ||||||
|     right:-10px; |      -moz-border-radius: 8px; | ||||||
|  |           border-radius: 8px; | ||||||
|  |   -webkit-box-shadow: 0 5px 10px rgba(0,0,0,.2); | ||||||
|  |      -moz-box-shadow: 0 5px 10px rgba(0,0,0,.2); | ||||||
|  |           box-shadow: 0 5px 10px rgba(0,0,0,.2); | ||||||
|  |   overflow:auto; | ||||||
|  |   max-height:300px; | ||||||
| } | } | ||||||
| 
 | 
 | ||||||
| .dhx_combo_option_img{ | .tt-suggestions { | ||||||
| 	position:relative; |  | ||||||
| 	top:1px; |  | ||||||
| 	margin:0px; |  | ||||||
| 	margin-left:2px; |  | ||||||
| 	left:0px; |  | ||||||
| 	width:18px; height:18px; |  | ||||||
| } | } | ||||||
| 
 | 
 | ||||||
| /* .combo_dhx_sel{ */ | .tt-suggestion { | ||||||
| /* .dhx_selected_option{ */ |   padding: 3px 20px; | ||||||
| /*    background-image: url("../static/images/bg_selection.gif") !important; */ |   font-size: 18px; | ||||||
| /*    background-position: bottom; */ |   line-height: 24px; | ||||||
| /*    background-repeat: repeat-x; */ | } | ||||||
| /*    color:black; */ |  | ||||||
| /* } */ |  | ||||||
| 
 | 
 | ||||||
|  | .tt-suggestion.tt-cursor { | ||||||
|  |   color: #fff; | ||||||
|  |   background-color: #0097cf; | ||||||
| 
 | 
 | ||||||
|  | } | ||||||
| 
 | 
 | ||||||
| /* .dhx_combo_img_rtl{ */ | .tt-suggestion p { | ||||||
| /* 	position:absolute; */ |   margin: 0; | ||||||
| /* 	top:0px; */ | } | ||||||
| /* 	left:1px; */ |  | ||||||
| /* 	width:17px; */ |  | ||||||
| /* 	height:20px; */ |  | ||||||
| /* } */ |  | ||||||
| /* .dhx_combo_option_img_rtl{ */ |  | ||||||
| /* 	float:right; */ |  | ||||||
| /* 	margin-right :0px; */ |  | ||||||
| /* 	width:18px; height:18px; */ |  | ||||||
| /* } */ |  | ||||||
| 
 |  | ||||||
| /* .dhx_combo_list_rtl{ */ |  | ||||||
| /* 	direction: rtl; */ |  | ||||||
| /* 	unicode-bidi : bidi-override; */ |  | ||||||
| /*    position:absolute; */ |  | ||||||
| /*    z-index:230; */ |  | ||||||
| /*    overflow-y:auto; */ |  | ||||||
| /*    overflow-x:hidden; */ |  | ||||||
| /*    border:1px solid black; */ |  | ||||||
| /*    height:100px; */ |  | ||||||
| /*    /\* font-family: Arial; *\/ */ |  | ||||||
| /*    font-size: 9pt; */ |  | ||||||
| /*    background-color: white; */ |  | ||||||
| /* } */ |  | ||||||
| /* .dhx_combo_list_rtl div{ */ |  | ||||||
| /* 	direction: rtl; */ |  | ||||||
| /* 	unicode-bidi : bidi-override; */ |  | ||||||
| /* 	padding:2px 2px 2px 2px; */ |  | ||||||
| /* } */ |  | ||||||
| /* .dhx_combo_list_rtl div div{ */ |  | ||||||
| /* 	float :right !important; */ |  | ||||||
| /* 	cursor:default; */ |  | ||||||
| /* } */ |  | ||||||
| /* .dhx_combo_list_rtl div img{ */ |  | ||||||
| /* 	float :right !important; */ |  | ||||||
| /* } */ |  | ||||||
| /* .dhx_combo_list_rtl div input{ */ |  | ||||||
| /* 	float :right !important; */ |  | ||||||
| /* } */ |  | ||||||
| 
 |  | ||||||
| /* .dhx_combo_box.dhx_skyblue{ */ |  | ||||||
| /* 	border:1px solid #a4bed4; */ |  | ||||||
| /* } */ |  | ||||||
| /* .dhx_combo_box.dhx_skyblue .dhx_combo_input { */ |  | ||||||
| /* 	font-family:Tahoma; */ |  | ||||||
| /* 	font-size: 11px; */ |  | ||||||
| /* 	padding:3px; */ |  | ||||||
| /* } */ |  | ||||||
| /* .dhx_combo_list.dhx_skyblue_list{ */ |  | ||||||
| /* 	background-color: #eaf2fb; */ |  | ||||||
| /* 	border:1px solid #a4bed4; */ |  | ||||||
| /* 	font-family:Tahoma; */ |  | ||||||
| /* 	font-size: 11px; */ |  | ||||||
| /* } */ |  | ||||||
| /* .dhx_combo_list.dhx_skyblue_list div{ */ |  | ||||||
| /* 	cursor:default; */ |  | ||||||
| /* 	padding:3px 4px; */ |  | ||||||
| /* } */ |  | ||||||
| /* .dhx_combo_list_rtl.dhx_skyblue_list{ */ |  | ||||||
| /*    background-color: #eaf2fb; */ |  | ||||||
| /* 	border:1px solid #a4bed4; */ |  | ||||||
| /* 	font-family:Tahoma; */ |  | ||||||
| /* 	font-size: 11px; */ |  | ||||||
| /* } */ |  | ||||||
| 
 | 
 | ||||||
|  | .twitter-typeahead { | ||||||
|  |   width:100%; | ||||||
|  | } | ||||||
| @ -1,126 +1,123 @@ | |||||||
| /* hledger web ui javascripts */ | /* hledger web ui javascript */ | ||||||
| /* depends on jquery, other support libs, and additional js inserted inline */ | /* depends on jquery etc. */ | ||||||
|  | 
 | ||||||
|  | // /* show/hide things based on locally-saved state */
 | ||||||
|  | // happens too late with large main content in chrome, visible glitch
 | ||||||
|  | // if (localStorage.getItem('sidebarVisible') == "false")
 | ||||||
|  | // 	$('#sidebar').hide();
 | ||||||
|  | // /* or request parameters */
 | ||||||
|  | // if ($.url.param('sidebar')=='' || $.url.param('sidebar')=='0')
 | ||||||
|  | //   $('#sidebar').hide();
 | ||||||
|  | // else if ($.url.param('sidebar')=='1')
 | ||||||
|  | //   $('#sidebar').show();
 | ||||||
|  | 
 | ||||||
|  | if ($.url.param('add')) { | ||||||
|  |   $('#addform').collapse('show'); | ||||||
|  |   $('#addform input[name=description]').focus(); | ||||||
|  | } | ||||||
| 
 | 
 | ||||||
| $(document).ready(function() { | $(document).ready(function() { | ||||||
| 
 | 
 | ||||||
|     /* show/hide things based on request parameters */ |     /* sidebar account hover handlers */ | ||||||
|     if ($.url.param('add')) addformToggle(); |     $('#sidebar td a').mouseenter(function(){ $(this).parent().addClass('mouseover'); }); | ||||||
|     else if ($.url.param('edit')) editformToggle(); |     $('#sidebar td').mouseleave(function(){ $(this).removeClass('mouseover'); }); | ||||||
|     if ($.url.param('accounts')=='0') $('#accounts').hide(); |  | ||||||
| 
 | 
 | ||||||
|     /* set up sidebar account mouse-over handlers */ |     /* keyboard shortcuts */ | ||||||
|     $('#sidebar p a, #sidebar td a').mouseenter(function(){ $(this).parent().addClass('mouseover'); }); |     $(document).bind('keydown', 'shift+/', function(){ $('#searchhelpmodal').modal('toggle'); return false; }); | ||||||
|     $('#sidebar p, #sidebar td').mouseleave(function(){ $(this).removeClass('mouseover'); }); |     $(document).bind('keydown', 'h',       function(){ $('#searchhelpmodal').modal('toggle'); return false; }); | ||||||
| 
 |     $(document).bind('keydown', 'j',       function(){ location.href = '/journal'; return false; }); | ||||||
|     /* set up various show/hide toggles */ |     $(document).bind('keydown', 's',       function(){ sidebarToggle(); return false; }); | ||||||
|     $('#search-help-link').click(function() { $('#search-help').slideToggle('fast'); event.preventDefault(); }); |     $(document).bind('keydown', 'a',       function(){ addformFocus(); return false; }); | ||||||
|     $('#sidebar-toggle-link').click(function() { $('#sidebar-content').slideToggle('fast'); event.preventDefault(); }); |     $('#addform input,#addform button,#addformlink').bind('keydown', 'esc', addformCancel); | ||||||
|     $('#all-postings-toggle-link').click(function() { $('.posting').toggle(); event.preventDefault(); }); |     $(document).bind('keydown', '/',       function(){ $('#searchform input').focus(); return false; }); | ||||||
|     $('.postings-toggle-link').click(function() { $(this).parent().parent().nextUntil(':not(.posting)').toggle(); event.preventDefault(); }); |     $('#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+-', addformDeletePosting); | ||||||
| 
 | 
 | ||||||
| }); | }); | ||||||
| 
 | 
 | ||||||
| function searchformToggle() { | function sidebarToggle() { | ||||||
|  var a = document.getElementById('addform'); |   console.log('sidebarToggle'); | ||||||
|  var e = document.getElementById('editform'); |   var visible = $('#sidebar').is(':visible'); | ||||||
|  var f = document.getElementById('searchform'); |   console.log('sidebar visibility was',visible); | ||||||
|  var i = document.getElementById('importform'); |   // if opening sidebar, start an ajax fetch of its content
 | ||||||
|  var c = document.getElementById('maincontent'); |   if (!visible) { | ||||||
|  var alink = document.getElementById('addformlink'); |     //console.log('getting sidebar content');
 | ||||||
|  var elink = document.getElementById('editformlink'); |     $.get("sidebar" | ||||||
|  var flink = document.getElementById('searchformlink'); |          ,null | ||||||
|  var ilink = document.getElementById('importformlink'); |          ,function(data) { | ||||||
|  var tlink = document.getElementById('transactionslink'); | 					  //console.log( "success" );
 | ||||||
| 
 |             $("#sidebar-body" ).html(data); | ||||||
|  if (f.style.display == 'none') { |           }) | ||||||
|   flink.style['font-weight'] = 'bold'; | 					.done(function() { | ||||||
|   f.style.display = 'block'; | 					  //console.log( "success 2" );
 | ||||||
|  } else { | 					}) | ||||||
|   flink.style['font-weight'] = 'normal'; | 					.fail(function() { | ||||||
|   f.style.display = 'none'; | 					  //console.log( "error" );
 | ||||||
|  } | 					}); | ||||||
|  return false; |   } | ||||||
|  | 	// localStorage.setItem('sidebarVisible', !visible);
 | ||||||
|  |   // set a cookie to communicate the new sidebar state to the server
 | ||||||
|  |   $.cookie('showsidebar', visible ? '0' : '1'); | ||||||
|  |   // horizontally slide the sidebar in or out
 | ||||||
|  |   // how to make it smooth, without delayed content pop-in ?
 | ||||||
|  |   //$('#sidebar').animate({'width': 'toggle'});
 | ||||||
|  |   //$('#sidebar').animate({'width': visible ? 'hide' : '+=20m'});
 | ||||||
|  |   //$('#sidebar-spacer').width(200);
 | ||||||
|  |   $('#sidebar').animate({'width': visible ? 'hide' : 'show'}); | ||||||
| } | } | ||||||
| 
 | 
 | ||||||
| function addformToggle(ev) { | function addformToggle() { | ||||||
|  var a = document.getElementById('addform'); |   if (location.pathname != '/journal') { | ||||||
|  var e = document.getElementById('editform'); |     location.href = '/journal?add=1'; | ||||||
|  var f = document.getElementById('searchform'); |   } | ||||||
|  var i = document.getElementById('importform'); |   else { | ||||||
|  var c = document.getElementById('maincontent'); |     $('#addform').collapse('toggle'); | ||||||
|  var alink = document.getElementById('addformlink'); |     $('#addform input[name=description]').focus(); | ||||||
|  var elink = document.getElementById('editformlink'); |   } | ||||||
|  var flink = document.getElementById('searchformlink'); |  | ||||||
|  var ilink = document.getElementById('importformlink'); |  | ||||||
|  var tlink = document.getElementById('transactionslink'); |  | ||||||
| 
 |  | ||||||
|  if (a.style.display == 'none') { |  | ||||||
|    if (alink) alink.style['font-weight'] = 'bold'; |  | ||||||
|    if (elink) elink.style['font-weight'] = 'normal'; |  | ||||||
|    if (ilink) ilink.style['font-weight'] = 'normal'; |  | ||||||
|    if (tlink) tlink.style['font-weight'] = 'normal'; |  | ||||||
|    if (a) a.style.display = 'block'; |  | ||||||
|    if (e) e.style.display = 'none'; |  | ||||||
|    if (i) i.style.display = 'none'; |  | ||||||
|    if (c) c.style.display = 'none'; |  | ||||||
|  } else { |  | ||||||
|    if (alink) alink.style['font-weight'] = 'normal'; |  | ||||||
|    if (elink) elink.style['font-weight'] = 'normal'; |  | ||||||
|    if (ilink) ilink.style['font-weight'] = 'normal'; |  | ||||||
|    if (tlink) tlink.style['font-weight'] = 'bold'; |  | ||||||
|    if (a) a.style.display = 'none'; |  | ||||||
|    if (e) e.style.display = 'none'; |  | ||||||
|    if (i) i.style.display = 'none'; |  | ||||||
|    if (c) c.style.display = 'block'; |  | ||||||
|  } |  | ||||||
|  return false; |  | ||||||
| } | } | ||||||
| 
 | 
 | ||||||
| function editformToggle(ev) { | function addformFocus() { | ||||||
|  var a = document.getElementById('addform'); |   if (location.pathname != '/journal') { | ||||||
|  var e = document.getElementById('editform'); |     location.href = '/journal?add=1'; | ||||||
|  var ej = document.getElementById('journalselect'); |   } | ||||||
|  var f = document.getElementById('searchform'); |   else { | ||||||
|  var i = document.getElementById('importform'); |     $('#addform').collapse('show'); | ||||||
|  var c = document.getElementById('maincontent'); |     $('#addform input[name=description]').focus(); | ||||||
|  var alink = document.getElementById('addformlink'); |   } | ||||||
|  var elink = document.getElementById('editformlink'); |  | ||||||
|  var flink = document.getElementById('searchformlink'); |  | ||||||
|  var ilink = document.getElementById('importformlink'); |  | ||||||
|  var tlink = document.getElementById('transactionslink'); |  | ||||||
| 
 |  | ||||||
|  if (e.style.display == 'none') { |  | ||||||
|   if (alink) alink.style['font-weight'] = 'normal'; |  | ||||||
|   if (elink) elink.style['font-weight'] = 'bold'; |  | ||||||
|   if (ilink) ilink.style['font-weight'] = 'normal'; |  | ||||||
|   if (tlink) tlink.style['font-weight'] = 'normal'; |  | ||||||
|   if (a) a.style.display = 'none'; |  | ||||||
|   if (i) i.style.display = 'none'; |  | ||||||
|   if (c) c.style.display = 'none'; |  | ||||||
|   if (e) e.style.display = 'block'; |  | ||||||
|   editformJournalSelect(ev); |  | ||||||
|  } else { |  | ||||||
|   if (alink) alink.style['font-weight'] = 'normal'; |  | ||||||
|   if (elink) elink.style['font-weight'] = 'normal'; |  | ||||||
|   if (ilink) ilink.style['font-weight'] = 'normal'; |  | ||||||
|    if (tlink) tlink.style['font-weight'] = 'bold'; |  | ||||||
|   if (a) a.style.display = 'none'; |  | ||||||
|   if (e) e.style.display = 'none'; |  | ||||||
|   if (i) i.style.display = 'none'; |  | ||||||
|   if (c) c.style.display = 'block'; |  | ||||||
|  } |  | ||||||
|  return false; |  | ||||||
| } | } | ||||||
| 
 | 
 | ||||||
| // Get the current event's target in a robust way.
 | function addformCancel() { | ||||||
| // http://www.quirksmode.org/js/events_properties.html
 |   $('#addform input[type=text]').typeahead('val',''); | ||||||
| function getTarget(ev) { |   $('#addform') | ||||||
|   var targ; |     .each( function(){ this.reset();} ) | ||||||
|   if (!ev) var ev = window.event; |     .collapse('hide'); | ||||||
|   if (ev.target) targ = ev.target; |   // try to keep keybindings working in safari
 | ||||||
|   else if (ev.srcElement) targ = ev.srcElement; |   //$('#addformlink').focus();
 | ||||||
|   if (targ.nodeType == 3) targ = targ.parentNode; | } | ||||||
|   return targ; | 
 | ||||||
|  | function addformAddPosting() { | ||||||
|  |   var rownum = $('#addform tr.posting').length + 1; | ||||||
|  |   // XXX duplicates markup in Common.hs
 | ||||||
|  |   // duplicate last row
 | ||||||
|  |   $('#addform > table').append($('#addform > table tr:last').clone()); | ||||||
|  |   // fix up second-last row
 | ||||||
|  |   $('#addform > table > tr.lastrow:first > td:last').html(''); | ||||||
|  |   $('#addform > table > tr.lastrow:first').removeClass('lastrow'); | ||||||
|  | 
 | ||||||
|  |   // fix up last row
 | ||||||
|  |   $('#addform table').append($('#addform table tr:last').clone()); | ||||||
|  |   //     '<tr class="posting">' +
 | ||||||
|  |   //     '<td style="padding-left:2em;">' +
 | ||||||
|  |   //     '<input id="account'+rownum+'" class="form-control input-lg" style="width:100%;" type="text"' +
 | ||||||
|  |   //     ' name=account'+rownum+'" placeholder="Account '+rownum+'">'
 | ||||||
|  |   // );
 | ||||||
|  | 
 | ||||||
|  |   // $('#addbtncell').appendTo($('#addform table tr:last'))
 | ||||||
|  |   //                  );
 | ||||||
|  | } | ||||||
|  | 
 | ||||||
|  | function addformDeletePosting() { | ||||||
| } | } | ||||||
| 
 | 
 | ||||||
| function editformJournalSelect(ev) { | function editformJournalSelect(ev) { | ||||||
| @ -142,36 +139,15 @@ function editformJournalSelect(ev) { | |||||||
|  return true; |  return true; | ||||||
| } | } | ||||||
| 
 | 
 | ||||||
| function importformToggle(ev) { | /* | ||||||
|  var a = document.getElementById('addform'); | // Get the current event's target in a robust way.
 | ||||||
|  var e = document.getElementById('editform'); | // http://www.quirksmode.org/js/events_properties.html
 | ||||||
|  var f = document.getElementById('searchform'); | function getTarget(ev) { | ||||||
|  var i = document.getElementById('importform'); |   var targ; | ||||||
|  var c = document.getElementById('maincontent'); |   if (!ev) var ev = window.event; | ||||||
|  var alink = document.getElementById('addformlink'); |   if (ev.target) targ = ev.target; | ||||||
|  var elink = document.getElementById('editformlink'); |   else if (ev.srcElement) targ = ev.srcElement; | ||||||
|  var flink = document.getElementById('searchformlink'); |   if (targ.nodeType == 3) targ = targ.parentNode; | ||||||
|  var ilink = document.getElementById('importformlink'); |   return targ; | ||||||
|  var tlink = document.getElementById('transactionslink'); |  | ||||||
| 
 |  | ||||||
|  if (i.style.display == 'none') { |  | ||||||
|    if (alink) alink.style['font-weight'] = 'normal'; |  | ||||||
|    if (elink) elink.style['font-weight'] = 'normal'; |  | ||||||
|    if (ilink) ilink.style['font-weight'] = 'bold'; |  | ||||||
|    if (tlink) tlink.style['font-weight'] = 'normal'; |  | ||||||
|    if (a) a.style.display = 'none'; |  | ||||||
|    if (e) e.style.display = 'none'; |  | ||||||
|    if (i) i.style.display = 'block'; |  | ||||||
|    if (c) c.style.display = 'none'; |  | ||||||
|  } else { |  | ||||||
|    if (alink) alink.style['font-weight'] = 'normal'; |  | ||||||
|    if (elink) elink.style['font-weight'] = 'normal'; |  | ||||||
|    if (ilink) ilink.style['font-weight'] = 'normal'; |  | ||||||
|    if (tlink) tlink.style['font-weight'] = 'bold'; |  | ||||||
|    if (a) a.style.display = 'none'; |  | ||||||
|    if (e) e.style.display = 'none'; |  | ||||||
|    if (i) i.style.display = 'none'; |  | ||||||
|    if (c) c.style.display = 'block'; |  | ||||||
|  } |  | ||||||
|  return false; |  | ||||||
| } | } | ||||||
|  | */ | ||||||
|  | |||||||
										
											Binary file not shown.
										
									
								
							| Before Width: | Height: | Size: 1.8 KiB | 
| @ -1,652 +0,0 @@ | |||||||
| /* |  | ||||||
| Version: 3.4.0 Timestamp: Tue May 14 08:27:33 PDT 2013 |  | ||||||
| */ |  | ||||||
| .select2-container { |  | ||||||
|     margin: 0; |  | ||||||
|     position: relative; |  | ||||||
|     display: inline-block; |  | ||||||
|     /* inline-block for ie7 */ |  | ||||||
|     zoom: 1; |  | ||||||
|     *display: inline; |  | ||||||
|     vertical-align: middle; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container, |  | ||||||
| .select2-drop, |  | ||||||
| .select2-search, |  | ||||||
| .select2-search input{ |  | ||||||
|   /* |  | ||||||
|     Force border-box so that % widths fit the parent |  | ||||||
|     container without overlap because of margin/padding. |  | ||||||
| 
 |  | ||||||
|     More Info : http://www.quirksmode.org/css/box.html |  | ||||||
|   */ |  | ||||||
|   -webkit-box-sizing: border-box; /* webkit */ |  | ||||||
|    -khtml-box-sizing: border-box; /* konqueror */ |  | ||||||
|      -moz-box-sizing: border-box; /* firefox */ |  | ||||||
|       -ms-box-sizing: border-box; /* ie */ |  | ||||||
|           box-sizing: border-box; /* css3 */ |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container .select2-choice { |  | ||||||
|     display: block; |  | ||||||
|     height: 26px; |  | ||||||
|     padding: 0 0 0 8px; |  | ||||||
|     overflow: hidden; |  | ||||||
|     position: relative; |  | ||||||
| 
 |  | ||||||
|     border: 1px solid #aaa; |  | ||||||
|     white-space: nowrap; |  | ||||||
|     line-height: 26px; |  | ||||||
|     color: #444; |  | ||||||
|     text-decoration: none; |  | ||||||
| 
 |  | ||||||
|     -webkit-border-radius: 4px; |  | ||||||
|        -moz-border-radius: 4px; |  | ||||||
|             border-radius: 4px; |  | ||||||
| 
 |  | ||||||
|     -webkit-background-clip: padding-box; |  | ||||||
|        -moz-background-clip: padding; |  | ||||||
|             background-clip: padding-box; |  | ||||||
| 
 |  | ||||||
|     -webkit-touch-callout: none; |  | ||||||
|       -webkit-user-select: none; |  | ||||||
|        -khtml-user-select: none; |  | ||||||
|          -moz-user-select: none; |  | ||||||
|           -ms-user-select: none; |  | ||||||
|               user-select: none; |  | ||||||
| 
 |  | ||||||
|     background-color: #fff; |  | ||||||
|     background-image: -webkit-gradient(linear, left bottom, left top, color-stop(0, #eeeeee), color-stop(0.5, white)); |  | ||||||
|     background-image: -webkit-linear-gradient(center bottom, #eeeeee 0%, white 50%); |  | ||||||
|     background-image: -moz-linear-gradient(center bottom, #eeeeee 0%, white 50%); |  | ||||||
|     background-image: -o-linear-gradient(bottom, #eeeeee 0%, #ffffff 50%); |  | ||||||
|     background-image: -ms-linear-gradient(top, #ffffff 0%, #eeeeee 50%); |  | ||||||
|     filter: progid:DXImageTransform.Microsoft.gradient(startColorstr = '#ffffff', endColorstr = '#eeeeee', GradientType = 0); |  | ||||||
|     background-image: linear-gradient(top, #ffffff 0%, #eeeeee 50%); |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container.select2-drop-above .select2-choice { |  | ||||||
|     border-bottom-color: #aaa; |  | ||||||
| 
 |  | ||||||
|     -webkit-border-radius:0 0 4px 4px; |  | ||||||
|        -moz-border-radius:0 0 4px 4px; |  | ||||||
|             border-radius:0 0 4px 4px; |  | ||||||
| 
 |  | ||||||
|     background-image: -webkit-gradient(linear, left bottom, left top, color-stop(0, #eeeeee), color-stop(0.9, white)); |  | ||||||
|     background-image: -webkit-linear-gradient(center bottom, #eeeeee 0%, white 90%); |  | ||||||
|     background-image: -moz-linear-gradient(center bottom, #eeeeee 0%, white 90%); |  | ||||||
|     background-image: -o-linear-gradient(bottom, #eeeeee 0%, white 90%); |  | ||||||
|     background-image: -ms-linear-gradient(top, #eeeeee 0%,#ffffff 90%); |  | ||||||
|     filter: progid:DXImageTransform.Microsoft.gradient( startColorstr='#ffffff', endColorstr='#eeeeee',GradientType=0 ); |  | ||||||
|     background-image: linear-gradient(top, #eeeeee 0%,#ffffff 90%); |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container.select2-allowclear .select2-choice span { |  | ||||||
|     margin-right: 42px; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container .select2-choice span { |  | ||||||
|     margin-right: 26px; |  | ||||||
|     display: block; |  | ||||||
|     overflow: hidden; |  | ||||||
| 
 |  | ||||||
|     white-space: nowrap; |  | ||||||
| 
 |  | ||||||
|     -ms-text-overflow: ellipsis; |  | ||||||
|      -o-text-overflow: ellipsis; |  | ||||||
|         text-overflow: ellipsis; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container .select2-choice abbr { |  | ||||||
|     display: none; |  | ||||||
|     width: 12px; |  | ||||||
|     height: 12px; |  | ||||||
|     position: absolute; |  | ||||||
|     right: 24px; |  | ||||||
|     top: 8px; |  | ||||||
| 
 |  | ||||||
|     font-size: 1px; |  | ||||||
|     text-decoration: none; |  | ||||||
| 
 |  | ||||||
|     border: 0; |  | ||||||
|     background: url('select2.png') right top no-repeat; |  | ||||||
|     cursor: pointer; |  | ||||||
|     outline: 0; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container.select2-allowclear .select2-choice abbr { |  | ||||||
|     display: inline-block; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container .select2-choice abbr:hover { |  | ||||||
|     background-position: right -11px; |  | ||||||
|     cursor: pointer; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-drop-mask { |  | ||||||
|     position: absolute; |  | ||||||
|     left: 0; |  | ||||||
|     top: 0; |  | ||||||
|     z-index: 9998; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-drop { |  | ||||||
|     width: 100%; |  | ||||||
|     margin-top:-1px; |  | ||||||
|     position: absolute; |  | ||||||
|     z-index: 9999; |  | ||||||
|     top: 100%; |  | ||||||
| 
 |  | ||||||
|     background: #fff; |  | ||||||
|     color: #000; |  | ||||||
|     border: 1px solid #aaa; |  | ||||||
|     border-top: 0; |  | ||||||
| 
 |  | ||||||
|     -webkit-border-radius: 0 0 4px 4px; |  | ||||||
|        -moz-border-radius: 0 0 4px 4px; |  | ||||||
|             border-radius: 0 0 4px 4px; |  | ||||||
| 
 |  | ||||||
|     -webkit-box-shadow: 0 4px 5px rgba(0, 0, 0, .15); |  | ||||||
|        -moz-box-shadow: 0 4px 5px rgba(0, 0, 0, .15); |  | ||||||
|             box-shadow: 0 4px 5px rgba(0, 0, 0, .15); |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-drop-auto-width { |  | ||||||
|     border-top: 1px solid #aaa; |  | ||||||
|     width: auto; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-drop-auto-width .select2-search { |  | ||||||
|     padding-top: 4px; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-drop.select2-drop-above { |  | ||||||
|     margin-top: 1px; |  | ||||||
|     border-top: 1px solid #aaa; |  | ||||||
|     border-bottom: 0; |  | ||||||
| 
 |  | ||||||
|     -webkit-border-radius: 4px 4px 0 0; |  | ||||||
|        -moz-border-radius: 4px 4px 0 0; |  | ||||||
|             border-radius: 4px 4px 0 0; |  | ||||||
| 
 |  | ||||||
|     -webkit-box-shadow: 0 -4px 5px rgba(0, 0, 0, .15); |  | ||||||
|        -moz-box-shadow: 0 -4px 5px rgba(0, 0, 0, .15); |  | ||||||
|             box-shadow: 0 -4px 5px rgba(0, 0, 0, .15); |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container .select2-choice div { |  | ||||||
|     display: inline-block; |  | ||||||
|     width: 18px; |  | ||||||
|     height: 100%; |  | ||||||
|     position: absolute; |  | ||||||
|     right: 0; |  | ||||||
|     top: 0; |  | ||||||
| 
 |  | ||||||
|     border-left: 1px solid #aaa; |  | ||||||
|     -webkit-border-radius: 0 4px 4px 0; |  | ||||||
|        -moz-border-radius: 0 4px 4px 0; |  | ||||||
|             border-radius: 0 4px 4px 0; |  | ||||||
| 
 |  | ||||||
|     -webkit-background-clip: padding-box; |  | ||||||
|        -moz-background-clip: padding; |  | ||||||
|             background-clip: padding-box; |  | ||||||
| 
 |  | ||||||
|     background: #ccc; |  | ||||||
|     background-image: -webkit-gradient(linear, left bottom, left top, color-stop(0, #ccc), color-stop(0.6, #eee)); |  | ||||||
|     background-image: -webkit-linear-gradient(center bottom, #ccc 0%, #eee 60%); |  | ||||||
|     background-image: -moz-linear-gradient(center bottom, #ccc 0%, #eee 60%); |  | ||||||
|     background-image: -o-linear-gradient(bottom, #ccc 0%, #eee 60%); |  | ||||||
|     background-image: -ms-linear-gradient(top, #cccccc 0%, #eeeeee 60%); |  | ||||||
|     filter: progid:DXImageTransform.Microsoft.gradient(startColorstr = '#eeeeee', endColorstr = '#cccccc', GradientType = 0); |  | ||||||
|     background-image: linear-gradient(top, #cccccc 0%, #eeeeee 60%); |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container .select2-choice div b { |  | ||||||
|     display: block; |  | ||||||
|     width: 100%; |  | ||||||
|     height: 100%; |  | ||||||
|     background: url('select2.png') no-repeat 0 1px; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-search { |  | ||||||
|     display: inline-block; |  | ||||||
|     width: 100%; |  | ||||||
|     min-height: 26px; |  | ||||||
|     margin: 0; |  | ||||||
|     padding-left: 4px; |  | ||||||
|     padding-right: 4px; |  | ||||||
| 
 |  | ||||||
|     position: relative; |  | ||||||
|     z-index: 10000; |  | ||||||
| 
 |  | ||||||
|     white-space: nowrap; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-search input { |  | ||||||
|     width: 100%; |  | ||||||
|     height: auto !important; |  | ||||||
|     min-height: 26px; |  | ||||||
|     padding: 4px 20px 4px 5px; |  | ||||||
|     margin: 0; |  | ||||||
| 
 |  | ||||||
|     outline: 0; |  | ||||||
|     font-family: sans-serif; |  | ||||||
|     font-size: 1em; |  | ||||||
| 
 |  | ||||||
|     border: 1px solid #aaa; |  | ||||||
|     -webkit-border-radius: 0; |  | ||||||
|        -moz-border-radius: 0; |  | ||||||
|             border-radius: 0; |  | ||||||
| 
 |  | ||||||
|     -webkit-box-shadow: none; |  | ||||||
|        -moz-box-shadow: none; |  | ||||||
|             box-shadow: none; |  | ||||||
| 
 |  | ||||||
|     background: #fff url('select2.png') no-repeat 100% -22px; |  | ||||||
|     background: url('select2.png') no-repeat 100% -22px, -webkit-gradient(linear, left bottom, left top, color-stop(0.85, white), color-stop(0.99, #eeeeee)); |  | ||||||
|     background: url('select2.png') no-repeat 100% -22px, -webkit-linear-gradient(center bottom, white 85%, #eeeeee 99%); |  | ||||||
|     background: url('select2.png') no-repeat 100% -22px, -moz-linear-gradient(center bottom, white 85%, #eeeeee 99%); |  | ||||||
|     background: url('select2.png') no-repeat 100% -22px, -o-linear-gradient(bottom, white 85%, #eeeeee 99%); |  | ||||||
|     background: url('select2.png') no-repeat 100% -22px, -ms-linear-gradient(top, #ffffff 85%, #eeeeee 99%); |  | ||||||
|     background: url('select2.png') no-repeat 100% -22px, linear-gradient(top, #ffffff 85%, #eeeeee 99%); |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-drop.select2-drop-above .select2-search input { |  | ||||||
|     margin-top: 4px; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-search input.select2-active { |  | ||||||
|     background: #fff url('select2-spinner.gif') no-repeat 100%; |  | ||||||
|     background: url('select2-spinner.gif') no-repeat 100%, -webkit-gradient(linear, left bottom, left top, color-stop(0.85, white), color-stop(0.99, #eeeeee)); |  | ||||||
|     background: url('select2-spinner.gif') no-repeat 100%, -webkit-linear-gradient(center bottom, white 85%, #eeeeee 99%); |  | ||||||
|     background: url('select2-spinner.gif') no-repeat 100%, -moz-linear-gradient(center bottom, white 85%, #eeeeee 99%); |  | ||||||
|     background: url('select2-spinner.gif') no-repeat 100%, -o-linear-gradient(bottom, white 85%, #eeeeee 99%); |  | ||||||
|     background: url('select2-spinner.gif') no-repeat 100%, -ms-linear-gradient(top, #ffffff 85%, #eeeeee 99%); |  | ||||||
|     background: url('select2-spinner.gif') no-repeat 100%, linear-gradient(top, #ffffff 85%, #eeeeee 99%); |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container-active .select2-choice, |  | ||||||
| .select2-container-active .select2-choices { |  | ||||||
|     border: 1px solid #5897fb; |  | ||||||
|     outline: none; |  | ||||||
| 
 |  | ||||||
|     -webkit-box-shadow: 0 0 5px rgba(0,0,0,.3); |  | ||||||
|        -moz-box-shadow: 0 0 5px rgba(0,0,0,.3); |  | ||||||
|             box-shadow: 0 0 5px rgba(0,0,0,.3); |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-dropdown-open .select2-choice { |  | ||||||
|     border-bottom-color: transparent; |  | ||||||
|     -webkit-box-shadow: 0 1px 0 #fff inset; |  | ||||||
|        -moz-box-shadow: 0 1px 0 #fff inset; |  | ||||||
|             box-shadow: 0 1px 0 #fff inset; |  | ||||||
| 
 |  | ||||||
|     -webkit-border-bottom-left-radius: 0; |  | ||||||
|         -moz-border-radius-bottomleft: 0; |  | ||||||
|             border-bottom-left-radius: 0; |  | ||||||
| 
 |  | ||||||
|     -webkit-border-bottom-right-radius: 0; |  | ||||||
|         -moz-border-radius-bottomright: 0; |  | ||||||
|             border-bottom-right-radius: 0; |  | ||||||
| 
 |  | ||||||
|     background-color: #eee; |  | ||||||
|     background-image: -webkit-gradient(linear, left bottom, left top, color-stop(0, white), color-stop(0.5, #eeeeee)); |  | ||||||
|     background-image: -webkit-linear-gradient(center bottom, white 0%, #eeeeee 50%); |  | ||||||
|     background-image: -moz-linear-gradient(center bottom, white 0%, #eeeeee 50%); |  | ||||||
|     background-image: -o-linear-gradient(bottom, white 0%, #eeeeee 50%); |  | ||||||
|     background-image: -ms-linear-gradient(top, #ffffff 0%,#eeeeee 50%); |  | ||||||
|     filter: progid:DXImageTransform.Microsoft.gradient( startColorstr='#eeeeee', endColorstr='#ffffff',GradientType=0 ); |  | ||||||
|     background-image: linear-gradient(top, #ffffff 0%,#eeeeee 50%); |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-dropdown-open.select2-drop-above .select2-choice, |  | ||||||
| .select2-dropdown-open.select2-drop-above .select2-choices { |  | ||||||
|     border: 1px solid #5897fb; |  | ||||||
|     border-top-color: transparent; |  | ||||||
| 
 |  | ||||||
|     background-image: -webkit-gradient(linear, left top, left bottom, color-stop(0, white), color-stop(0.5, #eeeeee)); |  | ||||||
|     background-image: -webkit-linear-gradient(center top, white 0%, #eeeeee 50%); |  | ||||||
|     background-image: -moz-linear-gradient(center top, white 0%, #eeeeee 50%); |  | ||||||
|     background-image: -o-linear-gradient(top, white 0%, #eeeeee 50%); |  | ||||||
|     background-image: -ms-linear-gradient(bottom, #ffffff 0%,#eeeeee 50%); |  | ||||||
|     filter: progid:DXImageTransform.Microsoft.gradient( startColorstr='#eeeeee', endColorstr='#ffffff',GradientType=0 ); |  | ||||||
|     background-image: linear-gradient(bottom, #ffffff 0%,#eeeeee 50%); |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-dropdown-open .select2-choice div { |  | ||||||
|     background: transparent; |  | ||||||
|     border-left: none; |  | ||||||
|     filter: none; |  | ||||||
| } |  | ||||||
| .select2-dropdown-open .select2-choice div b { |  | ||||||
|     background-position: -18px 1px; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| /* results */ |  | ||||||
| .select2-results { |  | ||||||
|     max-height: 200px; |  | ||||||
|     padding: 0 0 0 4px; |  | ||||||
|     margin: 4px 4px 4px 0; |  | ||||||
|     position: relative; |  | ||||||
|     overflow-x: hidden; |  | ||||||
|     overflow-y: auto; |  | ||||||
|     -webkit-tap-highlight-color: rgba(0,0,0,0); |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-results ul.select2-result-sub { |  | ||||||
|     margin: 0; |  | ||||||
|     padding-left: 0; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-results ul.select2-result-sub > li .select2-result-label { padding-left: 20px } |  | ||||||
| .select2-results ul.select2-result-sub ul.select2-result-sub > li .select2-result-label { padding-left: 40px } |  | ||||||
| .select2-results ul.select2-result-sub ul.select2-result-sub ul.select2-result-sub > li .select2-result-label { padding-left: 60px } |  | ||||||
| .select2-results ul.select2-result-sub ul.select2-result-sub ul.select2-result-sub ul.select2-result-sub > li .select2-result-label { padding-left: 80px } |  | ||||||
| .select2-results ul.select2-result-sub ul.select2-result-sub ul.select2-result-sub ul.select2-result-sub ul.select2-result-sub > li .select2-result-label { padding-left: 100px } |  | ||||||
| .select2-results ul.select2-result-sub ul.select2-result-sub ul.select2-result-sub ul.select2-result-sub ul.select2-result-sub ul.select2-result-sub > li .select2-result-label { padding-left: 110px } |  | ||||||
| .select2-results ul.select2-result-sub ul.select2-result-sub ul.select2-result-sub ul.select2-result-sub ul.select2-result-sub ul.select2-result-sub ul.select2-result-sub > li .select2-result-label { padding-left: 120px } |  | ||||||
| 
 |  | ||||||
| .select2-results li { |  | ||||||
|     list-style: none; |  | ||||||
|     display: list-item; |  | ||||||
|     background-image: none; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-results li.select2-result-with-children > .select2-result-label { |  | ||||||
|     font-weight: bold; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-results .select2-result-label { |  | ||||||
|     padding: 3px 7px 4px; |  | ||||||
|     margin: 0; |  | ||||||
|     cursor: pointer; |  | ||||||
| 
 |  | ||||||
|     min-height: 1em; |  | ||||||
| 
 |  | ||||||
|     -webkit-touch-callout: none; |  | ||||||
|       -webkit-user-select: none; |  | ||||||
|        -khtml-user-select: none; |  | ||||||
|          -moz-user-select: none; |  | ||||||
|           -ms-user-select: none; |  | ||||||
|               user-select: none; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-results .select2-highlighted { |  | ||||||
|     background: #3875d7; |  | ||||||
|     color: #fff; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-results li em { |  | ||||||
|     background: #feffde; |  | ||||||
|     font-style: normal; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-results .select2-highlighted em { |  | ||||||
|     background: transparent; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-results .select2-highlighted ul { |  | ||||||
|     background: white; |  | ||||||
|     color: #000; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| 
 |  | ||||||
| .select2-results .select2-no-results, |  | ||||||
| .select2-results .select2-searching, |  | ||||||
| .select2-results .select2-selection-limit { |  | ||||||
|     background: #f4f4f4; |  | ||||||
|     display: list-item; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| /* |  | ||||||
| disabled look for disabled choices in the results dropdown |  | ||||||
| */ |  | ||||||
| .select2-results .select2-disabled.select2-highlighted { |  | ||||||
|     color: #666; |  | ||||||
|     background: #f4f4f4; |  | ||||||
|     display: list-item; |  | ||||||
|     cursor: default; |  | ||||||
| } |  | ||||||
| .select2-results .select2-disabled { |  | ||||||
|   background: #f4f4f4; |  | ||||||
|   display: list-item; |  | ||||||
|   cursor: default; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-results .select2-selected { |  | ||||||
|     display: none; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-more-results.select2-active { |  | ||||||
|     background: #f4f4f4 url('select2-spinner.gif') no-repeat 100%; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-more-results { |  | ||||||
|     background: #f4f4f4; |  | ||||||
|     display: list-item; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| /* disabled styles */ |  | ||||||
| 
 |  | ||||||
| .select2-container.select2-container-disabled .select2-choice { |  | ||||||
|     background-color: #f4f4f4; |  | ||||||
|     background-image: none; |  | ||||||
|     border: 1px solid #ddd; |  | ||||||
|     cursor: default; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container.select2-container-disabled .select2-choice div { |  | ||||||
|     background-color: #f4f4f4; |  | ||||||
|     background-image: none; |  | ||||||
|     border-left: 0; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container.select2-container-disabled .select2-choice abbr { |  | ||||||
|     display: none; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| 
 |  | ||||||
| /* multiselect */ |  | ||||||
| 
 |  | ||||||
| .select2-container-multi .select2-choices { |  | ||||||
|     height: auto !important; |  | ||||||
|     height: 1%; |  | ||||||
|     margin: 0; |  | ||||||
|     padding: 0; |  | ||||||
|     position: relative; |  | ||||||
| 
 |  | ||||||
|     border: 1px solid #aaa; |  | ||||||
|     cursor: text; |  | ||||||
|     overflow: hidden; |  | ||||||
| 
 |  | ||||||
|     background-color: #fff; |  | ||||||
|     background-image: -webkit-gradient(linear, 0% 0%, 0% 100%, color-stop(1%, #eeeeee), color-stop(15%, #ffffff)); |  | ||||||
|     background-image: -webkit-linear-gradient(top, #eeeeee 1%, #ffffff 15%); |  | ||||||
|     background-image: -moz-linear-gradient(top, #eeeeee 1%, #ffffff 15%); |  | ||||||
|     background-image: -o-linear-gradient(top, #eeeeee 1%, #ffffff 15%); |  | ||||||
|     background-image: -ms-linear-gradient(top, #eeeeee 1%, #ffffff 15%); |  | ||||||
|     background-image: linear-gradient(top, #eeeeee 1%, #ffffff 15%); |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-locked { |  | ||||||
|   padding: 3px 5px 3px 5px !important; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container-multi .select2-choices { |  | ||||||
|     min-height: 26px; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container-multi.select2-container-active .select2-choices { |  | ||||||
|     border: 1px solid #5897fb; |  | ||||||
|     outline: none; |  | ||||||
| 
 |  | ||||||
|     -webkit-box-shadow: 0 0 5px rgba(0,0,0,.3); |  | ||||||
|        -moz-box-shadow: 0 0 5px rgba(0,0,0,.3); |  | ||||||
|             box-shadow: 0 0 5px rgba(0,0,0,.3); |  | ||||||
| } |  | ||||||
| .select2-container-multi .select2-choices li { |  | ||||||
|     float: left; |  | ||||||
|     list-style: none; |  | ||||||
| } |  | ||||||
| .select2-container-multi .select2-choices .select2-search-field { |  | ||||||
|     margin: 0; |  | ||||||
|     padding: 0; |  | ||||||
|     white-space: nowrap; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container-multi .select2-choices .select2-search-field input { |  | ||||||
|     padding: 5px; |  | ||||||
|     margin: 1px 0; |  | ||||||
| 
 |  | ||||||
|     font-family: sans-serif; |  | ||||||
|     font-size: 100%; |  | ||||||
|     color: #666; |  | ||||||
|     outline: 0; |  | ||||||
|     border: 0; |  | ||||||
|     -webkit-box-shadow: none; |  | ||||||
|        -moz-box-shadow: none; |  | ||||||
|             box-shadow: none; |  | ||||||
|     background: transparent !important; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container-multi .select2-choices .select2-search-field input.select2-active { |  | ||||||
|     background: #fff url('select2-spinner.gif') no-repeat 100% !important; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-default { |  | ||||||
|     color: #999 !important; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container-multi .select2-choices .select2-search-choice { |  | ||||||
|     padding: 3px 5px 3px 18px; |  | ||||||
|     margin: 3px 0 3px 5px; |  | ||||||
|     position: relative; |  | ||||||
| 
 |  | ||||||
|     line-height: 13px; |  | ||||||
|     color: #333; |  | ||||||
|     cursor: default; |  | ||||||
|     border: 1px solid #aaaaaa; |  | ||||||
| 
 |  | ||||||
|     -webkit-border-radius: 3px; |  | ||||||
|        -moz-border-radius: 3px; |  | ||||||
|             border-radius: 3px; |  | ||||||
| 
 |  | ||||||
|     -webkit-box-shadow: 0 0 2px #ffffff inset, 0 1px 0 rgba(0,0,0,0.05); |  | ||||||
|        -moz-box-shadow: 0 0 2px #ffffff inset, 0 1px 0 rgba(0,0,0,0.05); |  | ||||||
|             box-shadow: 0 0 2px #ffffff inset, 0 1px 0 rgba(0,0,0,0.05); |  | ||||||
| 
 |  | ||||||
|     -webkit-background-clip: padding-box; |  | ||||||
|        -moz-background-clip: padding; |  | ||||||
|             background-clip: padding-box; |  | ||||||
| 
 |  | ||||||
|     -webkit-touch-callout: none; |  | ||||||
|       -webkit-user-select: none; |  | ||||||
|        -khtml-user-select: none; |  | ||||||
|          -moz-user-select: none; |  | ||||||
|           -ms-user-select: none; |  | ||||||
|               user-select: none; |  | ||||||
| 
 |  | ||||||
|     background-color: #e4e4e4; |  | ||||||
|     filter: progid:DXImageTransform.Microsoft.gradient( startColorstr='#eeeeee', endColorstr='#f4f4f4', GradientType=0 ); |  | ||||||
|     background-image: -webkit-gradient(linear, 0% 0%, 0% 100%, color-stop(20%, #f4f4f4), color-stop(50%, #f0f0f0), color-stop(52%, #e8e8e8), color-stop(100%, #eeeeee)); |  | ||||||
|     background-image: -webkit-linear-gradient(top, #f4f4f4 20%, #f0f0f0 50%, #e8e8e8 52%, #eeeeee 100%); |  | ||||||
|     background-image: -moz-linear-gradient(top, #f4f4f4 20%, #f0f0f0 50%, #e8e8e8 52%, #eeeeee 100%); |  | ||||||
|     background-image: -o-linear-gradient(top, #f4f4f4 20%, #f0f0f0 50%, #e8e8e8 52%, #eeeeee 100%); |  | ||||||
|     background-image: -ms-linear-gradient(top, #f4f4f4 20%, #f0f0f0 50%, #e8e8e8 52%, #eeeeee 100%); |  | ||||||
|     background-image: linear-gradient(top, #f4f4f4 20%, #f0f0f0 50%, #e8e8e8 52%, #eeeeee 100%); |  | ||||||
| } |  | ||||||
| .select2-container-multi .select2-choices .select2-search-choice span { |  | ||||||
|     cursor: default; |  | ||||||
| } |  | ||||||
| .select2-container-multi .select2-choices .select2-search-choice-focus { |  | ||||||
|     background: #d4d4d4; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-search-choice-close { |  | ||||||
|     display: block; |  | ||||||
|     width: 12px; |  | ||||||
|     height: 13px; |  | ||||||
|     position: absolute; |  | ||||||
|     right: 3px; |  | ||||||
|     top: 4px; |  | ||||||
| 
 |  | ||||||
|     font-size: 1px; |  | ||||||
|     outline: none; |  | ||||||
|     background: url('select2.png') right top no-repeat; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container-multi .select2-search-choice-close { |  | ||||||
|     left: 3px; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container-multi .select2-choices .select2-search-choice .select2-search-choice-close:hover { |  | ||||||
|   background-position: right -11px; |  | ||||||
| } |  | ||||||
| .select2-container-multi .select2-choices .select2-search-choice-focus .select2-search-choice-close { |  | ||||||
|     background-position: right -11px; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| /* disabled styles */ |  | ||||||
| .select2-container-multi.select2-container-disabled .select2-choices{ |  | ||||||
|     background-color: #f4f4f4; |  | ||||||
|     background-image: none; |  | ||||||
|     border: 1px solid #ddd; |  | ||||||
|     cursor: default; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container-multi.select2-container-disabled .select2-choices .select2-search-choice { |  | ||||||
|     padding: 3px 5px 3px 5px; |  | ||||||
|     border: 1px solid #ddd; |  | ||||||
|     background-image: none; |  | ||||||
|     background-color: #f4f4f4; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-container-multi.select2-container-disabled .select2-choices .select2-search-choice .select2-search-choice-close {    display: none; |  | ||||||
|     background:none; |  | ||||||
| } |  | ||||||
| /* end multiselect */ |  | ||||||
| 
 |  | ||||||
| 
 |  | ||||||
| .select2-result-selectable .select2-match, |  | ||||||
| .select2-result-unselectable .select2-match { |  | ||||||
|     text-decoration: underline; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-offscreen, .select2-offscreen:focus { |  | ||||||
|     clip: rect(0 0 0 0); |  | ||||||
|     width: 1px; |  | ||||||
|     height: 1px; |  | ||||||
|     border: 0; |  | ||||||
|     margin: 0; |  | ||||||
|     padding: 0; |  | ||||||
|     overflow: hidden; |  | ||||||
|     position: absolute; |  | ||||||
|     outline: 0; |  | ||||||
|     left: 0px; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-display-none { |  | ||||||
|     display: none; |  | ||||||
| } |  | ||||||
| 
 |  | ||||||
| .select2-measure-scrollbar { |  | ||||||
|     position: absolute; |  | ||||||
|     top: -10000px; |  | ||||||
|     left: -10000px; |  | ||||||
|     width: 100px; |  | ||||||
|     height: 100px; |  | ||||||
|     overflow: scroll; |  | ||||||
| } |  | ||||||
| /* Retina-ize icons */ |  | ||||||
| 
 |  | ||||||
| @media only screen and (-webkit-min-device-pixel-ratio: 1.5), only screen and (min-resolution: 144dpi)  { |  | ||||||
|   .select2-search input, .select2-search-choice-close, .select2-container .select2-choice abbr, .select2-container .select2-choice div b { |  | ||||||
|       background-image: url('select2x2.png') !important; |  | ||||||
|       background-repeat: no-repeat !important; |  | ||||||
|       background-size: 60px 40px !important; |  | ||||||
|   } |  | ||||||
|   .select2-search input { |  | ||||||
|       background-position: 100% -21px !important; |  | ||||||
|   } |  | ||||||
| } |  | ||||||
										
											
												File diff suppressed because it is too large
												Load Diff
											
										
									
								
							
							
								
								
									
										22
									
								
								hledger-web/static/select2.min.js
									
									
									
									
										vendored
									
									
								
							
							
						
						
									
										22
									
								
								hledger-web/static/select2.min.js
									
									
									
									
										vendored
									
									
								
							
										
											
												File diff suppressed because one or more lines are too long
											
										
									
								
							
										
											Binary file not shown.
										
									
								
							| Before Width: | Height: | Size: 613 B | 
| @ -46,3 +46,49 @@ $newline never | |||||||
|             <script> |             <script> | ||||||
|                 window.attachEvent('onload',function(){CFInstall.check({mode:'overlay'})}) |                 window.attachEvent('onload',function(){CFInstall.check({mode:'overlay'})}) | ||||||
|         \<![endif]--> |         \<![endif]--> | ||||||
|  | 
 | ||||||
|  |         <div .modal.fade #searchhelpmodal tabindex="-1" role="dialog" aria-labelledby="searchHelpLabel" 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 #searchHelpLabel>Help | ||||||
|  |               <div .modal-body> | ||||||
|  |                 <div .row> | ||||||
|  |                   <div .col-xs-6> | ||||||
|  |                     <p> | ||||||
|  |                       <b>General | ||||||
|  |                       <ul> | ||||||
|  |                         <li> Journal shows general journal entries, representing zero-sum transactions between hierarchical accounts | ||||||
|  |                         <li> The resulting accounts and their final balances appear in the sidebar | ||||||
|  |                         <li> Parent account balances include subaccount balances | ||||||
|  |                         <li> Multiple currencies in balances are displayed one above the other | ||||||
|  |                         <li> Click account names to see transactions affecting that account, with running balance | ||||||
|  |                         <!-- <li> Click dates to see journal entries on that date --> | ||||||
|  |                     <p> | ||||||
|  |                       <b>Keyboard shortcuts | ||||||
|  |                       <ul> | ||||||
|  |                         <li> <b><tt>?, h</tt></b> - view this help; escape or click to exit | ||||||
|  |                         <li> <b><tt>s</tt></b> - toggle sidebar | ||||||
|  |                         <li> <b><tt>j</tt></b> - go to journal view | ||||||
|  |                         <li> <b><tt>ctrl-s, /</tt></b> - focus search form | ||||||
|  |                         <li> <b><tt>a</tt></b> - add a transaction; escape to cancel | ||||||
|  |                   <div .col-xs-6> | ||||||
|  |                     <p> | ||||||
|  |                       <b>Search | ||||||
|  |                       <ul> | ||||||
|  |                         <li> <b><tt>acct:REGEXP</tt></b> - filter on to/from account | ||||||
|  |                         <li> <b><tt>desc:REGEXP</tt></b> - filter on description | ||||||
|  |                         <li> <b><tt>date:PERIODEXP</tt></b>, <b><tt>date2:PERIODEXP</tt></b> - filter on date or secondary date | ||||||
|  |                         <li> <b><tt>code:REGEXP</tt></b> - filter on transaction's code (eg check number) | ||||||
|  |                         <li> <b><tt>status:*</tt></b>, <b><tt>status:!</tt></b>, <b><tt>status:</tt></b> - filter on transaction's status flag (eg cleared status) | ||||||
|  |                         <!-- <li> <b><tt>empty:BOOL</tt></b> - filter on whether amount is zero --> | ||||||
|  |                         <li> <b><tt>amt:N</tt></b>, <b><tt>amt:<N</tt></b>, <b><tt>amt:>N</tt></b> - filter on the unsigned amount magnitude. Or with a sign before N, filter on the signed value. (Single-commodity amounts only.) | ||||||
|  |                         <li> <b><tt>cur:REGEXP</tt></b> - filter on the currency/commodity symbol (must match all of it). Dollar sign must be written as <tt>\$</tt> | ||||||
|  |                         <li> <b><tt>tag:NAME</tt></b>, <b><tt>tag:NAME=REGEX</tt></b> - filter on tag name, or tag name and value | ||||||
|  |                         <!-- <li> <b><tt>depth:N</tt></b> - filter out accounts below this depth --> | ||||||
|  |                         <li> <b><tt>real:BOOL</tt></b> - filter on postings' real/virtual-ness | ||||||
|  |                         <li> Search patterns containing spaces must be enclosed in single or double quotes | ||||||
|  |                         <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> These search terms also work with command-line hledger | ||||||
|  | |||||||
		Loading…
	
		Reference in New Issue
	
	Block a user