web: Simplify HTML and CSS
This commit is contained in:
		
							parent
							
								
									df425802d4
								
							
						
					
					
						commit
						930b38a345
					
				| @ -29,7 +29,9 @@ getRegisterR = do | ||||
|       s2 = if m /= Any then ", filtered" else "" | ||||
|       header = a <> s1 <> s2 | ||||
| 
 | ||||
|   let r@(balancelabel,items) = accountTransactionsReport (reportopts_ $ cliopts_ opts) j m $ fromMaybe Any $ inAccountQuery qopts | ||||
|   let ropts = reportopts_ (cliopts_ opts) | ||||
|       acctQuery = fromMaybe Any (inAccountQuery qopts) | ||||
|       r@(balancelabel,items) = accountTransactionsReport ropts j m acctQuery | ||||
|       balancelabel' = if isJust (inAccount qopts) then balancelabel else "Total" | ||||
|   defaultLayout $ do | ||||
|     setTitle "register - hledger-web" | ||||
|  | ||||
| @ -38,7 +38,7 @@ addModal :: | ||||
| addModal addR j today = do | ||||
|   (addView, addEnctype) <- generateFormPost (addForm j today) | ||||
|   [whamlet| | ||||
| <div .modal.fade #addmodal tabindex="-1" role="dialog" aria-labelledby="addLabel" aria-hidden="true"> | ||||
| <div .modal #addmodal tabindex="-1" role="dialog" aria-labelledby="addLabel" aria-hidden="true"> | ||||
|   <div .modal-dialog .modal-lg> | ||||
|     <div .modal-content> | ||||
|       <div .modal-header> | ||||
|  | ||||
| @ -2,6 +2,7 @@ | ||||
| {-# LANGUAGE NamedFieldPuns #-} | ||||
| {-# LANGUAGE OverloadedStrings #-} | ||||
| {-# LANGUAGE QuasiQuotes #-} | ||||
| {-# LANGUAGE TemplateHaskell #-} | ||||
| 
 | ||||
| module Widget.Common | ||||
|   ( accountQuery | ||||
| @ -24,6 +25,7 @@ import Text.Blaze ((!), textValue) | ||||
| import qualified Text.Blaze.Html5 as H | ||||
| import qualified Text.Blaze.Html5.Attributes as A | ||||
| import Text.Blaze.Internal (preEscapedString) | ||||
| import Text.Hamlet (hamletFile) | ||||
| import Yesod | ||||
| 
 | ||||
| import Hledger | ||||
| @ -57,39 +59,13 @@ helplink topic label _ = H.a ! A.href u ! A.target "hledgerhelp" $ toHtml label | ||||
| 
 | ||||
| -- | Render a "BalanceReport" as html. | ||||
| balanceReportAsHtml :: Eq r => (r, r) -> r -> Bool -> Journal -> [QueryOpt] -> BalanceReport -> HtmlUrl r | ||||
| balanceReportAsHtml (journalR, registerR) here hideEmpty j qopts (items, total) = [hamlet| | ||||
| <tr :here == journalR:.inacct> | ||||
|   <td .top .acct> | ||||
|     <a href=@{journalR} :here == journalR:.inacct | ||||
|        title="Show general journal entries, most recent first"> | ||||
|       Journal | ||||
|   <td .top> | ||||
| $forall (acct, adisplay, aindent, abal) <- items | ||||
|   <tr .#{inacctClass acct} :isZeroMixedAmount abal && hideEmpty:.hide> | ||||
|     <td .acct :isZeroMixedAmount abal:.empty> | ||||
|       <div .ff-wrapper> | ||||
|         \#{indent aindent} | ||||
|         <a href="@?{acctLink acct}" .#{inacctClass acct} | ||||
|            title="Show transactions affecting this account and subaccounts"> | ||||
|           #{adisplay} | ||||
|         $if hasSubs acct | ||||
|           <a href="@?{acctOnlyLink acct}" .only .hidden-sm .hidden-xs | ||||
|              title="Show transactions affecting this account but not subaccounts">only | ||||
|     <td> | ||||
|       ^{mixedAmountAsHtml abal} | ||||
| <tr .total> | ||||
|   <td> | ||||
|   <td> | ||||
|     ^{mixedAmountAsHtml total} | ||||
| |] where | ||||
| balanceReportAsHtml (journalR, registerR) here hideEmpty j qopts (items, total) = | ||||
|   $(hamletFile "templates/balance-report.hamlet") | ||||
|   where | ||||
|     l = ledgerFromJournal Any j | ||||
|   inacctClass acct = case inAccountQuery qopts of | ||||
|     Just m' -> if m' `matchesAccount` acct then "inacct" else "" | ||||
|     Nothing -> "" :: Text | ||||
|   hasSubs acct = maybe True (not . null . asubs) (ledgerAccount l acct) | ||||
|     indent a = preEscapedString $ concat $ replicate (2 + 2 * a) " " | ||||
|   acctLink acct = (registerR, [("q", accountQuery acct)]) | ||||
|   acctOnlyLink acct = (registerR, [("q", accountOnlyQuery acct)]) | ||||
|     hasSubAccounts acct = maybe True (not . null . asubs) (ledgerAccount l acct) | ||||
|     matchesAcctSelector acct = Just True == ((`matchesAccount` acct) <$> inAccountQuery qopts) | ||||
| 
 | ||||
| accountQuery :: AccountName -> Text | ||||
| accountQuery = ("inacct:" <>) .  quoteIfSpaced | ||||
|  | ||||
| @ -39,9 +39,6 @@ | ||||
|   max-height:300px; | ||||
| } | ||||
| 
 | ||||
| .tt-suggestions { | ||||
| } | ||||
| 
 | ||||
| .tt-suggestion { | ||||
|   padding: 3px 20px; | ||||
|   font-size: 18px; | ||||
| @ -51,7 +48,6 @@ | ||||
| .tt-suggestion.tt-cursor { | ||||
|   color: #fff; | ||||
|   background-color: #0097cf; | ||||
| 
 | ||||
| } | ||||
| 
 | ||||
| .tt-suggestion p { | ||||
| @ -122,25 +118,11 @@ ul { | ||||
|     padding: 1px; | ||||
| } | ||||
| 
 | ||||
| #sidebar-menu .main-menu tr:hover > td > div > .only { | ||||
| #sidebar-menu .main-menu tr:hover .only { | ||||
|     visibility: visible; | ||||
| } | ||||
| 
 | ||||
| #sidebar-menu .main-menu .only:hover{ | ||||
|     border-left: none; | ||||
| } | ||||
| #sidebar-menu .main-menu .balance { | ||||
|     float: right; | ||||
| } | ||||
| 
 | ||||
| #sidebar-menu .main-menu .total { | ||||
|     border-left: none; | ||||
|     border-right: none; | ||||
|     border-bottom: none; | ||||
|     border-top: 1px solid black; | ||||
| } | ||||
| 
 | ||||
| #sidebar-menu .main-menu .inacct { | ||||
| #sidebar-menu .main-menu .inacct, #sidebar-menu .main-menu .inacct .acct-name { | ||||
|     font-weight: bold; | ||||
|     color: #11427D; | ||||
|     background-color: #f9f9f9; | ||||
| @ -157,7 +139,7 @@ ul { | ||||
|     vertical-align:bottom; | ||||
| } | ||||
| 
 | ||||
| .transactionsreport .nonhead { | ||||
| .transactionsreport .posting td { | ||||
|     border: none !important; | ||||
| } | ||||
| 
 | ||||
|  | ||||
| @ -167,7 +167,7 @@ function addformAddPosting() { | ||||
|     return; | ||||
|   } | ||||
| 
 | ||||
|   var prevLastRow = $('.amount-input:last'); | ||||
|   var prevLastRow = $('#addform .account-group:last'); | ||||
|   prevLastRow.off('keypress'); | ||||
| 
 | ||||
|   // Clone the currently last row
 | ||||
| @ -202,7 +202,7 @@ function addformDeletePosting() { | ||||
|   // delete last row
 | ||||
|   $('#addform .account-group:last').remove(); | ||||
|   if (focuslost) { | ||||
|     focus($('account-input:last')); | ||||
|     focus($('.account-input:last')); | ||||
|   } | ||||
|   // Rebind keypress
 | ||||
|   $('.amount-input:last').keypress(addformAddPosting); | ||||
|  | ||||
| @ -41,7 +41,7 @@ | ||||
| 
 | ||||
| <div .account-postings> | ||||
|   $forall (n, (acc, amt, accE, amtE)) <- msgs | ||||
|     <div .form-group .row .account-group #grp#{n}> | ||||
|     <div .form-group .row .account-group> | ||||
|       <div .col-md-8 .col-xs-8 .col-sm-8 :isJust accE:.has-error> | ||||
|         <input .account-input.form-control.input-lg.typeahead type=text | ||||
|           name=account placeholder="Account #{n}" value="#{acc}"> | ||||
| @ -65,6 +65,7 @@ $if length journals > 1 | ||||
|       $forall p <- journals | ||||
|         <option value=#{p}>#{p} | ||||
| <span .small style="padding-left:2em;"> | ||||
|   Enter a value in the last field for | ||||
|     <a href="#" onclick="addformAddPosting(); return false;">more | ||||
|     (or ctrl +, ctrl -) | ||||
|   Enter a value in the last field for # | ||||
|   <a href="#" onclick="addformAddPosting(); return false;"> | ||||
|     more | ||||
|   \ (or ctrl +, ctrl -) | ||||
|  | ||||
							
								
								
									
										25
									
								
								hledger-web/templates/balance-report.hamlet
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										25
									
								
								hledger-web/templates/balance-report.hamlet
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,25 @@ | ||||
| <tr :here == journalR:.inacct> | ||||
|   <td .top .acct> | ||||
|     <a href=@{journalR} :here == journalR:.inacct | ||||
|        title="Show general journal entries, most recent first"> | ||||
|       Journal | ||||
|   <td .top> | ||||
| $forall (acct, adisplay, aindent, abal) <- items | ||||
|   <tr | ||||
|      :matchesAcctSelector acct:.inacct | ||||
|      :isZeroMixedAmount abal && hideEmpty:.hide> | ||||
|     <td .acct :isZeroMixedAmount abal:.empty> | ||||
|       <div .ff-wrapper> | ||||
|         \#{indent aindent} | ||||
|         <a.acct-name href="@?{(registerR, [("q", accountQuery acct)])}" | ||||
|            title="Show transactions affecting this account and subaccounts"> | ||||
|           #{adisplay} | ||||
|         $if hasSubAccounts acct | ||||
|           <a href="@?{(registerR, [("q", accountOnlyQuery acct)])}" .only.hidden-sm.hidden-xs | ||||
|              title="Show transactions affecting this account but not subaccounts">only | ||||
|     <td> | ||||
|       ^{mixedAmountAsHtml abal} | ||||
| <tr .total> | ||||
|   <td> | ||||
|   <td> | ||||
|     ^{mixedAmountAsHtml total} | ||||
| @ -1,4 +1,6 @@ | ||||
| <h2 #contenttitle>#{title'} | ||||
| <h2> | ||||
|   #{title'} | ||||
| 
 | ||||
| <a #addformlink href="#" role="button" style="cursor:pointer; margin-top:1em;" | ||||
|    data-toggle="modal" data-target="#addmodal" title="Add a new transaction to the journal"> | ||||
|   Add a transaction | ||||
| @ -13,21 +15,23 @@ | ||||
| 
 | ||||
|     $forall (torig, _, split, _, amt, _) <- items | ||||
|       <tr .title #transaction-#{tindex torig}> | ||||
|         <td .date nowrap>#{show (tdate torig)} | ||||
|         <td .description colspan=2>#{textElideRight 60 (tdescription torig)} | ||||
|         <td .date nowrap> | ||||
|           #{show (tdate torig)} | ||||
|         <td colspan=2> | ||||
|           #{textElideRight 60 (tdescription torig)} | ||||
|         <td .amount style="text-align:right;"> | ||||
|           $if not split && not (isZeroMixedAmount amt) | ||||
|             \^{mixedAmountAsHtml amt} | ||||
|             ^{mixedAmountAsHtml amt} | ||||
| 
 | ||||
|       $forall Posting { paccount = acc, pamount = amt } <- tpostings torig | ||||
|         <tr .item.posting title="#{show torig}"> | ||||
|           <td .nonhead> | ||||
|           <td .nonhead> | ||||
|           <td .nonhead> | ||||
|         <tr .posting title="#{show torig}"> | ||||
|           <td> | ||||
|           <td> | ||||
|           <td> | ||||
|               | ||||
|             <a href="@?{acctlink acc}##{tindex torig}" title="#{acc}"> | ||||
|               #{elideAccountName 40 acc} | ||||
|           <td .amount .nonhead style="text-align:right;"> | ||||
|           <td .amount style="text-align:right;"> | ||||
|             ^{mixedAmountAsHtml amt} | ||||
| 
 | ||||
| ^{addModal AddR j today} | ||||
|  | ||||
| @ -1,4 +1,4 @@ | ||||
| <h2 #contenttitle> | ||||
| <h2> | ||||
|   #{header} | ||||
| 
 | ||||
| <div .hidden-xs> | ||||
| @ -19,15 +19,18 @@ | ||||
| 
 | ||||
|     <tbody> | ||||
|       $forall (torig, tacct, split, acct, amt, bal) <- items | ||||
|         <tr ##{tindex torig} .item title="#{show torig}" style="vertical-align:top;"> | ||||
|         <tr ##{tindex torig} title="#{show torig}" style="vertical-align:top;"> | ||||
|           <td .date> | ||||
|             <a href="@{JournalR}#transaction-#{tindex torig}"> | ||||
|               #{show (tdate tacct)} | ||||
|           <td .description title="#{show torig}">#{textElideRight 30 (tdescription tacct)} | ||||
|           <td .account>#{elideRight 40 acct} | ||||
|           <td title="#{show torig}"> | ||||
|             #{textElideRight 30 (tdescription tacct)} | ||||
|           <td .account> | ||||
|             #{elideRight 40 acct} | ||||
|           <td .amount style="text-align:right; white-space:nowrap;"> | ||||
|             $if not split || not (isZeroMixedAmount amt) | ||||
|               ^{mixedAmountAsHtml amt} | ||||
|           <td .balance style="text-align:right;">^{mixedAmountAsHtml bal} | ||||
|           <td style="text-align:right;"> | ||||
|             ^{mixedAmountAsHtml bal} | ||||
| 
 | ||||
| ^{addModal AddR j today} | ||||
|  | ||||
		Loading…
	
		Reference in New Issue
	
	Block a user