web: Extract html into external files
This commit is contained in:
		
							parent
							
								
									4c8d7de602
								
							
						
					
					
						commit
						ee36b529e7
					
				| @ -98,7 +98,7 @@ $forall t <- ts | |||||||
|   <span .#{c}>#{t} |   <span .#{c}>#{t} | ||||||
|   <br> |   <br> | ||||||
| |] where | |] where | ||||||
|   ts = T.lines . T.pack $ showMixedAmountWithoutPrice b |   ts = lines (showMixedAmountWithoutPrice b) | ||||||
|   c = case isNegativeMixedAmount b of |   c = case isNegativeMixedAmount b of | ||||||
|     Just True -> "negative amount" :: Text |     Just True -> "negative amount" :: Text | ||||||
|     _         -> "positive amount" |     _         -> "positive amount" | ||||||
|  | |||||||
| @ -1,6 +1,10 @@ | |||||||
| {-# LANGUAGE OverloadedStrings, QuasiQuotes, NamedFieldPuns #-} |  | ||||||
| -- | /journal handlers. | -- | /journal handlers. | ||||||
| 
 | 
 | ||||||
|  | {-# LANGUAGE NamedFieldPuns #-} | ||||||
|  | {-# LANGUAGE OverloadedStrings #-} | ||||||
|  | {-# LANGUAGE QuasiQuotes #-} | ||||||
|  | {-# LANGUAGE TemplateHaskell #-} | ||||||
|  | 
 | ||||||
| module Handler.JournalR where | module Handler.JournalR where | ||||||
| 
 | 
 | ||||||
| import Import | import Import | ||||||
| @ -19,55 +23,14 @@ getJournalR :: Handler Html | |||||||
| getJournalR = do | getJournalR = do | ||||||
|   VD{j, m, opts, qopts} <- getViewData |   VD{j, m, opts, qopts} <- getViewData | ||||||
|   -- XXX like registerReportAsHtml |   -- XXX like registerReportAsHtml | ||||||
|  | 
 | ||||||
|   let title = case inAccount qopts of |   let title = case inAccount qopts of | ||||||
|         Nothing -> "General Journal" |         Nothing -> "General Journal" | ||||||
|         Just (a, inclsubs) -> "Transactions in " <> a <> if inclsubs then "" else " (excluding subaccounts)" |         Just (a, inclsubs) -> "Transactions in " <> a <> if inclsubs then "" else " (excluding subaccounts)" | ||||||
|       title' = title <> if m /= Any then ", filtered" else "" |       title' = title <> if m /= Any then ", filtered" else "" | ||||||
|       maincontent = transactionsReportAsHtml $ journalTransactionsReport (reportopts_ $ cliopts_ opts) j m |       acctlink a = (RegisterR, [("q", accountQuery a)]) | ||||||
|  |       (_, items) = journalTransactionsReport (reportopts_ $ cliopts_ opts) j m | ||||||
|  | 
 | ||||||
|   defaultLayout $ do |   defaultLayout $ do | ||||||
|     setTitle "journal - hledger-web" |     setTitle "journal - hledger-web" | ||||||
|     toWidget [hamlet| |     $(widgetFile "journal") | ||||||
| <div .row> |  | ||||||
|   <h2 #contenttitle>#{title'} |  | ||||||
|   <!-- p>Journal entries record movements of commodities between accounts. --> |  | ||||||
|   <a #addformlink role="button" style="cursor:pointer; margin-top:1em;" data-toggle="modal" data-target="#addmodal" title="Add a new transaction to the journal" href="#">Add a transaction |  | ||||||
| <div .table-responsive> |  | ||||||
|   ^{maincontent} |  | ||||||
|     |] |  | ||||||
| 
 |  | ||||||
| -- | Render a "TransactionsReport" as html for the formatted journal view. |  | ||||||
| transactionsReportAsHtml :: (w, [TransactionsReportItem]) -> HtmlUrl AppRoute |  | ||||||
| transactionsReportAsHtml (_,items) = [hamlet| |  | ||||||
| <table .transactionsreport .table .table-condensed> |  | ||||||
|  <thead> |  | ||||||
|   <th .date style="text-align:left;"> |  | ||||||
|    Date |  | ||||||
|   <th .description style="text-align:left;">Description |  | ||||||
|   <th .account style="text-align:left;">Account |  | ||||||
|   <th .amount style="text-align:right;">Amount |  | ||||||
|  $forall i <- items |  | ||||||
|   ^{transactionReportItem i} |  | ||||||
|  |] |  | ||||||
| 
 |  | ||||||
| transactionReportItem :: TransactionsReportItem -> HtmlUrl AppRoute |  | ||||||
| transactionReportItem (torig, _, split, _, amt, _) = [hamlet| |  | ||||||
| <tr .title #transaction-#{tindex torig}> |  | ||||||
|  <td .date nowrap>#{date} |  | ||||||
|  <td .description colspan=2>#{textElideRight 60 desc} |  | ||||||
|  <td .amount style="text-align:right;"> |  | ||||||
|   $if showamt |  | ||||||
|    \^{mixedAmountAsHtml amt} |  | ||||||
| $forall p' <- tpostings torig |  | ||||||
|  <tr .item .posting title="#{show torig}"> |  | ||||||
|   <td .nonhead> |  | ||||||
|   <td .nonhead> |  | ||||||
|   <td .nonhead> |  | ||||||
|      |  | ||||||
|    <a href="@?{acctlink (paccount p')}##{tindex torig}" title="#{paccount p'}">#{elideAccountName 40 $ paccount p'} |  | ||||||
|   <td .amount .nonhead style="text-align:right;">^{mixedAmountAsHtml $ pamount p'} |  | ||||||
| |] |  | ||||||
|      where |  | ||||||
|        acctlink a = (RegisterR, [("q", accountQuery a)]) |  | ||||||
|        (date, desc) = (show $ tdate torig, tdescription torig) |  | ||||||
|        showamt = not split || not (isZeroMixedAmount amt) |  | ||||||
| 
 |  | ||||||
|  | |||||||
| @ -1,6 +1,11 @@ | |||||||
| {-# LANGUAGE ScopedTypeVariables, OverloadedStrings, QuasiQuotes, NamedFieldPuns #-} |  | ||||||
| -- | /register handlers. | -- | /register handlers. | ||||||
| 
 | 
 | ||||||
|  | {-# LANGUAGE NamedFieldPuns #-} | ||||||
|  | {-# LANGUAGE OverloadedStrings #-} | ||||||
|  | {-# LANGUAGE QuasiQuotes #-} | ||||||
|  | {-# LANGUAGE ScopedTypeVariables #-} | ||||||
|  | {-# LANGUAGE TemplateHaskell #-} | ||||||
|  | 
 | ||||||
| module Handler.RegisterR where | module Handler.RegisterR where | ||||||
| 
 | 
 | ||||||
| import Import | import Import | ||||||
| @ -9,6 +14,7 @@ import Data.Time | |||||||
| import Data.List (intersperse) | import Data.List (intersperse) | ||||||
| import qualified Data.Text as T | import qualified Data.Text as T | ||||||
| import Safe (headMay) | import Safe (headMay) | ||||||
|  | import Text.Hamlet (hamletFile) | ||||||
| 
 | 
 | ||||||
| import Handler.Common (mixedAmountAsHtml, numberTransactionsReportItems) | import Handler.Common (mixedAmountAsHtml, numberTransactionsReportItems) | ||||||
| 
 | 
 | ||||||
| @ -20,132 +26,29 @@ import Hledger.Web.WebOptions | |||||||
| getRegisterR :: Handler Html | getRegisterR :: Handler Html | ||||||
| getRegisterR = do | getRegisterR = do | ||||||
|   VD{j, m, opts, qopts} <- getViewData |   VD{j, m, opts, qopts} <- getViewData | ||||||
|   let title = a <> s1 <> s2 |   let (a,inclsubs) = fromMaybe ("all accounts",True) $ inAccount qopts | ||||||
|         where |  | ||||||
|           (a,inclsubs) = fromMaybe ("all accounts",True) $ inAccount qopts |  | ||||||
|       s1 = if inclsubs then "" else " (excluding subaccounts)" |       s1 = if inclsubs then "" else " (excluding subaccounts)" | ||||||
|       s2 = if m /= Any then ", filtered" else "" |       s2 = if m /= Any then ", filtered" else "" | ||||||
|   defaultLayout $ do |       header = a <> s1 <> s2 | ||||||
|     setTitle "register - hledger-web" |  | ||||||
|     _ <- toWidget [hamlet|<h2 #contenttitle>#{title}|] |  | ||||||
|     toWidget $ registerReportHtml qopts $ accountTransactionsReport (reportopts_ $ cliopts_ opts) j m $ fromMaybe Any $ inAccountQuery qopts |  | ||||||
| 
 | 
 | ||||||
| -- | Generate html for an account register, including a balance chart and transaction list. |   let r@(balancelabel,items) = accountTransactionsReport (reportopts_ $ cliopts_ opts) j m $ fromMaybe Any $ inAccountQuery qopts | ||||||
| registerReportHtml :: [QueryOpt] -> TransactionsReport -> HtmlUrl AppRoute |       balancelabel' = if isJust (inAccount qopts) then balancelabel else "Total" | ||||||
| registerReportHtml qopts r = [hamlet| |       evenodd x = if even x then "even" else "odd" :: Text | ||||||
|  <div .hidden-xs> |       datetransition newm newd | ||||||
|   ^{registerChartHtml $ transactionsReportByCommodity r} |         | newm = "newmonth" | ||||||
|  ^{registerItemsHtml qopts r} |  | ||||||
| |] |  | ||||||
| 
 |  | ||||||
| -- | Generate html for a transaction list from an "TransactionsReport". |  | ||||||
| registerItemsHtml :: [QueryOpt] -> TransactionsReport -> HtmlUrl AppRoute |  | ||||||
| registerItemsHtml qopts (balancelabel,items) = [hamlet| |  | ||||||
| <div .table-responsive> |  | ||||||
|  <table.registerreport .table .table-striped .table-condensed> |  | ||||||
|   <thead> |  | ||||||
|    <tr> |  | ||||||
|     <th style="text-align:left;"> |  | ||||||
|      Date |  | ||||||
|      <span .glyphicon .glyphicon-chevron-up> |  | ||||||
|     <th style="text-align:left;">Description |  | ||||||
|     <th style="text-align:left;">To/From Account(s) |  | ||||||
|     <th style="text-align:right; white-space:normal;">Amount Out/In |  | ||||||
|     <th style="text-align:right; white-space:normal;">#{balancelabel'} |  | ||||||
|   $forall i <- numberTransactionsReportItems items |  | ||||||
|    ^{itemAsHtml i} |  | ||||||
|  |] |  | ||||||
|  where |  | ||||||
|    insomeacct = isJust $ inAccount qopts |  | ||||||
|    balancelabel' = if insomeacct then balancelabel else "Total" |  | ||||||
| 
 |  | ||||||
|    itemAsHtml :: (Int, Bool, Bool, TransactionsReportItem) -> HtmlUrl AppRoute |  | ||||||
|    itemAsHtml (n, newd, newm, (torig, tacct, split, acct, amt, bal)) = [hamlet| |  | ||||||
| <tr ##{tindex torig} .item.#{evenodd}.#{firstposting}.#{datetransition} title="#{show torig}" style="vertical-align:top;"> |  | ||||||
|  <td .date> |  | ||||||
|   <a href="@{JournalR}#transaction-#{tindex torig}">#{date} |  | ||||||
|  <td .description title="#{show torig}">#{textElideRight 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} |  | ||||||
| |] |  | ||||||
|      where |  | ||||||
|        evenodd = if even n then "even" else "odd" :: Text |  | ||||||
|        datetransition | newm = "newmonth" |  | ||||||
|         | newd = "newday" |         | newd = "newday" | ||||||
|         | otherwise = "" :: Text |         | otherwise = "" :: Text | ||||||
|        (firstposting, date, desc) = (False, show $ tdate tacct, tdescription tacct) | 
 | ||||||
|        showamt = not split || not (isZeroMixedAmount amt) |   defaultLayout $ do | ||||||
|  |     setTitle "register - hledger-web" | ||||||
|  |     $(widgetFile "register") | ||||||
| 
 | 
 | ||||||
| -- | Generate javascript/html for a register balance line chart based on | -- | Generate javascript/html for a register balance line chart based on | ||||||
| -- the provided "TransactionsReportItem"s. | -- the provided "TransactionsReportItem"s. | ||||||
| registerChartHtml :: [(CommoditySymbol, (String, [TransactionsReportItem]))] -> HtmlUrl AppRoute | registerChartHtml :: [(CommoditySymbol, (String, [TransactionsReportItem]))] -> HtmlUrl AppRoute | ||||||
| registerChartHtml percommoditytxnreports = | registerChartHtml percommoditytxnreports = $(hamletFile "templates/chart.hamlet") | ||||||
|  -- have to make sure plot is not called when our container (maincontent) |  -- have to make sure plot is not called when our container (maincontent) | ||||||
|  -- is hidden, eg with add form toggled |  -- is hidden, eg with add form toggled | ||||||
|  [hamlet| |  | ||||||
| <label #register-chart-label style=""><br> |  | ||||||
| <div #register-chart style="height:150px; margin-bottom:1em; display:block;"> |  | ||||||
| <script type=text/javascript> |  | ||||||
|  \$(document).ready(function() { |  | ||||||
|    var $chartdiv = $('#register-chart'); |  | ||||||
|    if ($chartdiv.is(':visible')) { |  | ||||||
|      \$('#register-chart-label').text('#{charttitle}'); |  | ||||||
|      var seriesData = [ |  | ||||||
|       $forall (c,(_,items)) <- percommoditytxnreports |  | ||||||
|        /* we render each commodity using two series: |  | ||||||
|         * one with extra data points added to show a stepped balance line */ |  | ||||||
|        { |  | ||||||
|         data: [ |  | ||||||
|           $forall i <- reverse items |  | ||||||
|            [ |  | ||||||
|             #{dayToJsTimestamp $ triDate i}, |  | ||||||
|             #{simpleMixedAmountQuantity $ triCommodityBalance c i} |  | ||||||
|            ], |  | ||||||
|         ], |  | ||||||
|         label: '#{shownull $ T.unpack c}', |  | ||||||
|         color: #{colorForCommodity c}, |  | ||||||
|         lines: { |  | ||||||
|           show: true, |  | ||||||
|           steps: true, |  | ||||||
|         }, |  | ||||||
|         points: { |  | ||||||
|           show: false, |  | ||||||
|         }, |  | ||||||
|         clickable: false, |  | ||||||
|         hoverable: false, |  | ||||||
|        }, |  | ||||||
|        /* and one with the original data, showing one clickable, hoverable point per transaction */ |  | ||||||
|        { |  | ||||||
|         data: [ |  | ||||||
|           $forall i <- reverse items |  | ||||||
|            [ |  | ||||||
|             #{dayToJsTimestamp $ triDate i}, |  | ||||||
|             #{simpleMixedAmountQuantity $ triCommodityBalance c i}, |  | ||||||
|             '#{showMixedAmountWithZeroCommodity $ triCommodityAmount c i}', |  | ||||||
|             '#{showMixedAmountWithZeroCommodity $ triCommodityBalance c i}', |  | ||||||
|             '#{concat $ intersperse "\\n" $ lines  $ show $ triOrigTransaction i}', |  | ||||||
|             #{tindex $ triOrigTransaction i} |  | ||||||
|            ], |  | ||||||
|           /* [] */ |  | ||||||
|         ], |  | ||||||
|         label: '', |  | ||||||
|         color: #{colorForCommodity c}, |  | ||||||
|         lines: { |  | ||||||
|           show: false, |  | ||||||
|         }, |  | ||||||
|         points: { |  | ||||||
|           show: true, |  | ||||||
|         }, |  | ||||||
|        }, |  | ||||||
|      ] |  | ||||||
|      var plot = registerChart($chartdiv, seriesData); |  | ||||||
|      \$chartdiv.bind("plotclick", registerChartClick); |  | ||||||
|    }; |  | ||||||
|  }); |  | ||||||
| |] |  | ||||||
|  where |  where | ||||||
|    charttitle = case maybe "" (fst.snd) $ headMay percommoditytxnreports of |    charttitle = case maybe "" (fst.snd) $ headMay percommoditytxnreports of | ||||||
|      "" -> "" |      "" -> "" | ||||||
|  | |||||||
							
								
								
									
										59
									
								
								hledger-web/templates/chart.hamlet
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										59
									
								
								hledger-web/templates/chart.hamlet
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,59 @@ | |||||||
|  | <label #register-chart-label style=""><br> | ||||||
|  | <div #register-chart style="height:150px; margin-bottom:1em; display:block;"> | ||||||
|  | <script type=text/javascript> | ||||||
|  |  \$(document).ready(function() { | ||||||
|  |    var $chartdiv = $('#register-chart'); | ||||||
|  |    if ($chartdiv.is(':visible')) { | ||||||
|  |      \$('#register-chart-label').text('#{charttitle}'); | ||||||
|  |      var seriesData = [ | ||||||
|  |       $forall (c,(_,items)) <- percommoditytxnreports | ||||||
|  |        /* we render each commodity using two series: | ||||||
|  |         * one with extra data points added to show a stepped balance line */ | ||||||
|  |        { | ||||||
|  |         data: [ | ||||||
|  |           $forall i <- reverse items | ||||||
|  |            [ | ||||||
|  |             #{dayToJsTimestamp $ triDate i}, | ||||||
|  |             #{simpleMixedAmountQuantity $ triCommodityBalance c i} | ||||||
|  |            ], | ||||||
|  |         ], | ||||||
|  |         label: '#{shownull $ T.unpack c}', | ||||||
|  |         color: #{colorForCommodity c}, | ||||||
|  |         lines: { | ||||||
|  |           show: true, | ||||||
|  |           steps: true, | ||||||
|  |         }, | ||||||
|  |         points: { | ||||||
|  |           show: false, | ||||||
|  |         }, | ||||||
|  |         clickable: false, | ||||||
|  |         hoverable: false, | ||||||
|  |        }, | ||||||
|  |        /* and one with the original data, showing one clickable, hoverable point per transaction */ | ||||||
|  |        { | ||||||
|  |         data: [ | ||||||
|  |           $forall i <- reverse items | ||||||
|  |            [ | ||||||
|  |             #{dayToJsTimestamp $ triDate i}, | ||||||
|  |             #{simpleMixedAmountQuantity $ triCommodityBalance c i}, | ||||||
|  |             '#{showMixedAmountWithZeroCommodity $ triCommodityAmount c i}', | ||||||
|  |             '#{showMixedAmountWithZeroCommodity $ triCommodityBalance c i}', | ||||||
|  |             '#{concat $ intersperse "\\n" $ lines  $ show $ triOrigTransaction i}', | ||||||
|  |             #{tindex $ triOrigTransaction i} | ||||||
|  |            ], | ||||||
|  |           /* [] */ | ||||||
|  |         ], | ||||||
|  |         label: '', | ||||||
|  |         color: #{colorForCommodity c}, | ||||||
|  |         lines: { | ||||||
|  |           show: false, | ||||||
|  |         }, | ||||||
|  |         points: { | ||||||
|  |           show: true, | ||||||
|  |         }, | ||||||
|  |        }, | ||||||
|  |      ] | ||||||
|  |      var plot = registerChart($chartdiv, seriesData); | ||||||
|  |      \$chartdiv.bind("plotclick", registerChartClick); | ||||||
|  |    }; | ||||||
|  |  }); | ||||||
							
								
								
									
										32
									
								
								hledger-web/templates/journal.hamlet
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										32
									
								
								hledger-web/templates/journal.hamlet
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,32 @@ | |||||||
|  | <div .row> | ||||||
|  |   <h2 #contenttitle>#{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 | ||||||
|  | 
 | ||||||
|  | <div .table-responsive> | ||||||
|  |   <table .transactionsreport .table .table-condensed> | ||||||
|  |     <thead> | ||||||
|  |       <th .date style="text-align:left;">Date | ||||||
|  |       <th .description style="text-align:left;">Description | ||||||
|  |       <th .account style="text-align:left;">Account | ||||||
|  |       <th .amount style="text-align:right;">Amount | ||||||
|  | 
 | ||||||
|  |     $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 .amount style="text-align:right;"> | ||||||
|  |           $if not split || not (isZeroMixedAmount amt) | ||||||
|  |             \^{mixedAmountAsHtml amt} | ||||||
|  | 
 | ||||||
|  |       $forall Posting { paccount = acc, pamount = amt } <- tpostings torig | ||||||
|  |         <tr .item.posting title="#{show torig}"> | ||||||
|  |           <td .nonhead> | ||||||
|  |           <td .nonhead> | ||||||
|  |           <td .nonhead> | ||||||
|  |               | ||||||
|  |             <a href="@?{acctlink acc}##{tindex torig}" title="#{acc}"> | ||||||
|  |               #{elideAccountName 40 acc} | ||||||
|  |           <td .amount .nonhead style="text-align:right;"> | ||||||
|  |             ^{mixedAmountAsHtml amt} | ||||||
							
								
								
									
										32
									
								
								hledger-web/templates/register.hamlet
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										32
									
								
								hledger-web/templates/register.hamlet
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,32 @@ | |||||||
|  | <h2 #contenttitle> | ||||||
|  |   #{header} | ||||||
|  | 
 | ||||||
|  | <div .hidden-xs> | ||||||
|  |   ^{registerChartHtml $ transactionsReportByCommodity r} | ||||||
|  | 
 | ||||||
|  | <div .table-responsive> | ||||||
|  |   <table.registerreport .table .table-striped .table-condensed> | ||||||
|  |     <thead> | ||||||
|  |       <tr> | ||||||
|  |         <th style="text-align:left;"> | ||||||
|  |           Date | ||||||
|  |           <span .glyphicon .glyphicon-chevron-up> | ||||||
|  |         <th style="text-align:left;">Description | ||||||
|  |         <th style="text-align:left;">To/From Account(s) | ||||||
|  |         <th style="text-align:right; white-space:normal;">Amount Out/In | ||||||
|  |         <th style="text-align:right; white-space:normal;"> | ||||||
|  |           #{balancelabel'} | ||||||
|  | 
 | ||||||
|  |     <tbody> | ||||||
|  |       $forall (n, newd, newm, (torig, tacct, split, acct, amt, bal)) <- numberTransactionsReportItems items | ||||||
|  |         <tr ##{tindex torig} .item.#{evenodd n}.#{datetransition newm newd} | ||||||
|  |             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 .amount style="text-align:right; white-space:nowrap;"> | ||||||
|  |             $if not split || not (isZeroMixedAmount amt) | ||||||
|  |               \^{mixedAmountAsHtml amt} | ||||||
|  |           <td .balance style="text-align:right;">^{mixedAmountAsHtml bal} | ||||||
		Loading…
	
		Reference in New Issue
	
	Block a user