web: Replace RecordWildCards with NamedFieldPuns, remove unused parameters

This commit is contained in:
Jakub Zárybnický 2018-06-09 12:09:31 +02:00
parent 1d2b3521f6
commit d760904982
6 changed files with 27 additions and 27 deletions

View File

@ -1,5 +1,5 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE CPP, LambdaCase, MultiParamTypeClasses, NamedFieldPuns, OverloadedStrings, RecordWildCards, QuasiQuotes, TemplateHaskell, TypeFamilies, TypeSynonymInstances, FlexibleInstances #-}
{-# LANGUAGE CPP, LambdaCase, MultiParamTypeClasses, NamedFieldPuns, OverloadedStrings, QuasiQuotes, TemplateHaskell, TypeFamilies, TypeSynonymInstances, FlexibleInstances #-}
-- | Define the web application's foundation, in the usual Yesod style.
-- See a default Yesod app's comments for more details of each part.
@ -87,7 +87,7 @@ instance Yesod App where
defaultLayout widget = do
master <- getYesod
lastmsg <- getMessage
vd@VD{..} <- getViewData
VD{j, opts} <- getViewData
-- We break up the default layout into two components:
-- default-layout is the contents of the body tag, and
@ -237,8 +237,8 @@ getLastMessage = cached getMessage
-- add form dialog, part of the default template
-- | Add transaction form.
addform :: ViewData -> HtmlUrl AppRoute
addform VD{..} = [hamlet|
addform :: Journal -> HtmlUrl AppRoute
addform j = [hamlet|
<script>
jQuery(document).ready(function() {

View File

@ -1,4 +1,4 @@
{-# LANGUAGE CPP, FlexibleContexts, OverloadedStrings, QuasiQuotes, RecordWildCards, ScopedTypeVariables, TypeFamilies #-}
{-# LANGUAGE CPP, FlexibleContexts, OverloadedStrings, QuasiQuotes, NamedFieldPuns, ScopedTypeVariables, TypeFamilies #-}
-- | Add form data & handler. (The layout and js are defined in
-- Foundation so that the add form can be in the default layout for
-- all views.)
@ -47,7 +47,7 @@ addForm today j = AddForm
postAddForm :: Handler Html
postAddForm = do
-- 1. process the fixed fields with yesod-form
VD{..} <- getViewData
VD{today, j} <- getViewData
formresult <- runInputPostResult (addForm today j)
ok <- case formresult of

View File

@ -1,4 +1,4 @@
{-# LANGUAGE CPP, OverloadedStrings, QuasiQuotes, RecordWildCards #-}
{-# LANGUAGE CPP, OverloadedStrings, QuasiQuotes, NamedFieldPuns #-}
-- | Common page components and rendering helpers.
-- For global page layout, see Application.hs.
@ -44,7 +44,7 @@ hledgerLayout vd title content = do
-- | Global toolbar/heading area.
topbar :: ViewData -> HtmlUrl AppRoute
topbar VD{..} = [hamlet|
topbar VD{j, showsidebar} = [hamlet|
<div#spacer .#{showsm} .#{showmd} .col-xs-2>
<h1>
<button .visible-xs .btn .btn-default type="button" data-toggle="offcanvas">
@ -60,7 +60,7 @@ topbar VD{..} = [hamlet|
-- | The sidebar used on most views.
sidebar :: ViewData -> HtmlUrl AppRoute
sidebar vd@VD{..} =
sidebar vd@VD{am, here, j, opts, showsidebar} =
[hamlet|
<div #sidebar-menu .#{showmd} .#{showsm} .sidebar-offcanvas>
<table .main-menu .table>
@ -99,7 +99,7 @@ sidebar vd@VD{..} =
-- | Search form for entering custom queries to filter journal data.
searchform :: ViewData -> HtmlUrl AppRoute
searchform VD{..} = [hamlet|
searchform VD{q, here} = [hamlet|
<div#searchformdiv .row>
<form#searchform .form-inline method=GET>
<div .form-group .col-md-12 .col-sm-12 .col-xs-12>
@ -174,7 +174,7 @@ helplink topic label = [hamlet|
-- | Render a "BalanceReport" as html.
balanceReportAsHtml :: ViewData -> BalanceReport -> HtmlUrl AppRoute
balanceReportAsHtml VD{..} (items, total) =
balanceReportAsHtml VD{j, qopts} (items, total) =
[hamlet|
$forall i <- items
^{itemAsHtml i}

View File

@ -1,4 +1,4 @@
{-# LANGUAGE OverloadedStrings, QuasiQuotes, RecordWildCards #-}
{-# LANGUAGE OverloadedStrings, QuasiQuotes, NamedFieldPuns #-}
-- | /journal handlers.
module Handler.JournalR where
@ -18,7 +18,7 @@ import Hledger.Web.WebOptions
-- | The formatted journal view, with sidebar.
getJournalR :: Handler Html
getJournalR = do
vd@VD{..} <- getViewData
vd@VD{j, m, opts, qopts} <- getViewData
let -- XXX like registerReportAsHtml
title = case inAccount qopts of
Nothing -> "General Journal" <> s2
@ -26,7 +26,7 @@ getJournalR = do
where s1 = if inclsubs then "" else " (excluding subaccounts)"
where
s2 = if m /= Any then ", filtered" else ""
maincontent = journalTransactionsReportAsHtml vd $ journalTransactionsReport (reportopts_ $ cliopts_ opts) j m
maincontent = journalTransactionsReportAsHtml $ journalTransactionsReport (reportopts_ $ cliopts_ opts) j m
hledgerLayout vd "journal" [hamlet|
<div .row>
<h2 #contenttitle>#{title}
@ -40,8 +40,8 @@ postJournalR :: Handler Html
postJournalR = postAddForm
-- | Render a "TransactionsReport" as html for the formatted journal view.
journalTransactionsReportAsHtml :: ViewData -> TransactionsReport -> HtmlUrl AppRoute
journalTransactionsReportAsHtml vd (_,items) = [hamlet|
journalTransactionsReportAsHtml :: TransactionsReport -> HtmlUrl AppRoute
journalTransactionsReportAsHtml (_,items) = [hamlet|
<table .transactionsreport .table .table-condensed>
<thead>
<th .date style="text-align:left;">
@ -50,11 +50,11 @@ journalTransactionsReportAsHtml vd (_,items) = [hamlet|
<th .account style="text-align:left;">Account
<th .amount style="text-align:right;">Amount
$forall i <- numberTransactionsReportItems items
^{itemAsHtml vd i}
^{itemAsHtml i}
|]
where
itemAsHtml :: ViewData -> (Int, Bool, Bool, Bool, TransactionsReportItem) -> HtmlUrl AppRoute
itemAsHtml VD{..} (_, _, _, _, (torig, _, split, _, amt, _)) = [hamlet|
itemAsHtml :: (Int, Bool, Bool, Bool, TransactionsReportItem) -> HtmlUrl AppRoute
itemAsHtml (_, _, _, _, (torig, _, split, _, amt, _)) = [hamlet|
<tr .title #transaction-#{tindex torig}>
<td .date nowrap>#{date}
<td .description colspan=2>#{textElideRight 60 desc}

View File

@ -1,4 +1,4 @@
{-# LANGUAGE OverloadedStrings, QuasiQuotes, RecordWildCards #-}
{-# LANGUAGE OverloadedStrings, QuasiQuotes, NamedFieldPuns #-}
-- | /register handlers.
module Handler.RegisterR where
@ -23,7 +23,7 @@ import Hledger.Web.WebOptions
-- | The main journal/account register view, with accounts sidebar.
getRegisterR :: Handler Html
getRegisterR = do
vd@VD{..} <- getViewData
vd@VD{j, m, opts, qopts} <- getViewData
let title = a <> s1 <> s2
where
(a,inclsubs) = fromMaybe ("all accounts",True) $ inAccount qopts
@ -46,7 +46,7 @@ registerReportHtml vd r = [hamlet|
-- | Generate html for a transaction list from an "TransactionsReport".
registerItemsHtml :: ViewData -> TransactionsReport -> HtmlUrl AppRoute
registerItemsHtml vd (balancelabel,items) = [hamlet|
registerItemsHtml VD{qopts} (balancelabel,items) = [hamlet|
<div .table-responsive>
<table.registerreport .table .table-striped .table-condensed>
<thead>
@ -59,14 +59,14 @@ registerItemsHtml vd (balancelabel,items) = [hamlet|
<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 vd i}
^{itemAsHtml i}
|]
where
insomeacct = isJust $ inAccount $ qopts vd
insomeacct = isJust $ inAccount qopts
balancelabel' = if insomeacct then balancelabel else "Total"
itemAsHtml :: ViewData -> (Int, Bool, Bool, Bool, TransactionsReportItem) -> HtmlUrl AppRoute
itemAsHtml VD{..} (n, newd, newm, _, (torig, tacct, split, acct, amt, bal)) = [hamlet|
itemAsHtml :: (Int, Bool, 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}

View File

@ -104,4 +104,4 @@ $newline never
$maybe m <- lastmsg
$if isPrefixOf "Errors" (renderHtml m)
<div #message>#{m}
^{addform vd}
^{addform j}