cln: hlint: Clean up section related warnings.

This commit is contained in:
Stephen Morgan 2021-08-27 21:13:28 +10:00 committed by Simon Michael
parent 1a534e485c
commit 32dad455fd
7 changed files with 19 additions and 23 deletions

View File

@ -16,8 +16,6 @@
- ignore: {name: "Use camelCase"} - ignore: {name: "Use camelCase"}
- ignore: {name: "Use list comprehension"} - ignore: {name: "Use list comprehension"}
- ignore: {name: "Use fewer imports"} - ignore: {name: "Use fewer imports"}
- ignore: {name: "Use tuple-section"}
- ignore: {name: "Use section"}
# Specify additional command line arguments # Specify additional command line arguments

View File

@ -225,7 +225,7 @@ splitSpan (DaysOfWeek days@(n:_)) ds
wheel = (\x -> zipWith (-) (tail x) x) . concat . zipWith fmap (fmap (+) [0,7..]) . repeat $ days wheel = (\x -> zipWith (-) (tail x) x) . concat . zipWith fmap (fmap (+) [0,7..]) . repeat $ days
split = splitspan' (repeat startofday) (fmap (flip applyN nextday) wheel) split = splitspan' (repeat startofday) (fmap (`applyN` nextday) wheel)
splitSpan (DayOfYear m n) s = splitspan (nthdayofyearcontaining m n) (applyN (n-1) nextday . applyN (m-1) nextmonth . nextyear) s splitSpan (DayOfYear m n) s = splitspan (nthdayofyearcontaining m n) (applyN (n-1) nextday . applyN (m-1) nextmonth . nextyear) s
-- splitSpan (WeekOfYear n) s = splitspan startofweek (applyN n nextweek) s -- splitSpan (WeekOfYear n) s = splitspan startofweek (applyN n nextweek) s

View File

@ -1001,7 +1001,7 @@ getAmount rules record currency p1IsVirtual n =
assignments' | any isnumbered assignments = filter isnumbered assignments assignments' | any isnumbered assignments = filter isnumbered assignments
| otherwise = assignments | otherwise = assignments
where where
isnumbered (f,_) = T.any (flip elem ['0'..'9']) f isnumbered (f,_) = T.any isDigit f
-- if there's more than one value and only some are zeros, discard the zeros -- if there's more than one value and only some are zeros, discard the zeros
assignments'' assignments''

View File

@ -442,7 +442,7 @@ budgetReportAsCsv
++ concat [[rowtot, budgettot] | row_total_] ++ concat [[rowtot, budgettot] | row_total_]
++ concat [[rowavg, budgetavg] | average_] ++ concat [[rowavg, budgetavg] | average_]
joinNames = fmap ((:) (render row)) joinNames = fmap (render row :)
-- tests -- tests

View File

@ -5,6 +5,7 @@
{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
module Hledger.Web.Handler.RegisterR where module Hledger.Web.Handler.RegisterR where
@ -78,7 +79,7 @@ preferReal ps
elideRightDecorated :: Int -> [(Maybe d, Char)] -> [(Maybe d, Char)] elideRightDecorated :: Int -> [(Maybe d, Char)] -> [(Maybe d, Char)]
elideRightDecorated width s = elideRightDecorated width s =
if length s > width if length s > width
then take (width - 2) s ++ map ((,) Nothing) ".." then take (width - 2) s ++ map (Nothing,) ".."
else s else s
undecorateLinks :: [(Maybe acct, char)] -> [(acct, ([char], [char]))] undecorateLinks :: [(Maybe acct, char)] -> [(acct, ([char], [char]))]
@ -92,10 +93,8 @@ undecorateLinks xs0@(x:_) =
_ -> error "link name not decorated with account" -- PARTIAL: _ -> error "link name not decorated with account" -- PARTIAL:
decorateLinks :: [(acct, ([char], [char]))] -> [(Maybe acct, char)] decorateLinks :: [(acct, ([char], [char]))] -> [(Maybe acct, char)]
decorateLinks = decorateLinks = concatMap $ \(acct, (name, comma)) ->
concatMap map (Just acct,) name ++ map (Nothing,) comma
(\(acct, (name, comma)) ->
map ((,) (Just acct)) name ++ map ((,) Nothing) comma)
-- | Generate javascript/html for a register balance line chart based on -- | Generate javascript/html for a register balance line chart based on
-- the provided "AccountTransactionsReportItem"s. -- the provided "AccountTransactionsReportItem"s.

View File

@ -515,14 +515,12 @@ multiBalanceReportAsCsv opts@ReportOpts{..} =
(if transpose_ then transpose else id) . uncurry (++) . multiBalanceReportAsCsv' opts (if transpose_ then transpose else id) . uncurry (++) . multiBalanceReportAsCsv' opts
multiBalanceReportAsCsv' :: ReportOpts -> MultiBalanceReport -> (CSV, CSV) multiBalanceReportAsCsv' :: ReportOpts -> MultiBalanceReport -> (CSV, CSV)
multiBalanceReportAsCsv' opts@ReportOpts{..} multiBalanceReportAsCsv' opts@ReportOpts{..} (PeriodicReport colspans items tr) =
(PeriodicReport colspans items tr) = ( ("account" : ["commodity" | commodity_column_] ++ map showDateSpan colspans
flip (,) totalrows $
("account" : ["commodity" | commodity_column_] ++ map showDateSpan colspans
++ ["total" | row_total_] ++ ["total" | row_total_]
++ ["average" | average_] ++ ["average" | average_]
) : ) : concatMap (fullRowAsTexts (accountNameDrop drop_ . prrFullName)) items
concatMap (fullRowAsTexts (accountNameDrop drop_ . prrFullName)) items , totalrows)
where where
fullRowAsTexts render row = (render row :) <$> multiBalanceRowAsCsvText opts row fullRowAsTexts render row = (render row :) <$> multiBalanceRowAsCsvText opts row
totalrows totalrows

View File

@ -1,6 +1,7 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ParallelListComp #-} {-# LANGUAGE ParallelListComp #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecordWildCards #-}
{-| {-|
@ -119,7 +120,7 @@ roi CliOpts{rawopts_=rawopts, reportspec_=rspec@ReportSpec{_rsReportOpts=ReportO
priceDates = dbg3 "priceDates" $ nub $ filter (spanContainsDate span) priceDirectiveDates priceDates = dbg3 "priceDates" $ nub $ filter (spanContainsDate span) priceDirectiveDates
cashFlow = cashFlow =
((map (\d -> (d,nullmixedamt)) priceDates)++) $ ((map (,nullmixedamt) priceDates)++) $
cashFlowApplyCostValue $ cashFlowApplyCostValue $
calculateCashFlow trans (And [ Not investmentsQuery calculateCashFlow trans (And [ Not investmentsQuery
, Not pnlQuery , Not pnlQuery