cln: hlint: Clean up hlint warnings not already ignored in hlint.yaml.
This commit is contained in:
parent
063aaf35b5
commit
fed75c58e9
@ -840,7 +840,7 @@ weekday = do
|
|||||||
show wday <> " in " <> show (weekdays ++ weekdayabbrevs)
|
show wday <> " in " <> show (weekdays ++ weekdayabbrevs)
|
||||||
|
|
||||||
weekdaysp :: TextParser m [Int]
|
weekdaysp :: TextParser m [Int]
|
||||||
weekdaysp = fmap head . groupBy (==) . sort <$> sepBy1 weekday (string' ",")
|
weekdaysp = fmap head . group . sort <$> sepBy1 weekday (string' ",")
|
||||||
|
|
||||||
-- | Parse a period expression, specifying a date span and optionally
|
-- | Parse a period expression, specifying a date span and optionally
|
||||||
-- a reporting interval. Requires a reference "today" date for
|
-- a reporting interval. Requires a reference "today" date for
|
||||||
|
|||||||
@ -183,7 +183,7 @@ parseQuery d = parseQueryList d . words'' prefixes
|
|||||||
-- 4. then all terms are AND'd together
|
-- 4. then all terms are AND'd together
|
||||||
parseQueryList :: Day -> [T.Text] -> Either String (Query, [QueryOpt])
|
parseQueryList :: Day -> [T.Text] -> Either String (Query, [QueryOpt])
|
||||||
parseQueryList d termstrs = do
|
parseQueryList d termstrs = do
|
||||||
eterms <- sequence $ map (parseQueryTerm d) termstrs
|
eterms <- mapM (parseQueryTerm d) termstrs
|
||||||
let (pats, opts) = partitionEithers eterms
|
let (pats, opts) = partitionEithers eterms
|
||||||
(descpats, pats') = partition queryIsDesc pats
|
(descpats, pats') = partition queryIsDesc pats
|
||||||
(acctpats, pats'') = partition queryIsAcct pats'
|
(acctpats, pats'') = partition queryIsAcct pats'
|
||||||
@ -361,14 +361,14 @@ simplifyQuery q =
|
|||||||
simplify (And []) = Any
|
simplify (And []) = Any
|
||||||
simplify (And [q]) = simplify q
|
simplify (And [q]) = simplify q
|
||||||
simplify (And qs) | same qs = simplify $ head qs
|
simplify (And qs) | same qs = simplify $ head qs
|
||||||
| any (==None) qs = None
|
| None `elem` qs = None
|
||||||
| all queryIsDate qs = Date $ spansIntersect $ mapMaybe queryTermDateSpan qs
|
| all queryIsDate qs = Date $ spansIntersect $ mapMaybe queryTermDateSpan qs
|
||||||
| otherwise = And $ concat $ [map simplify dateqs, map simplify otherqs]
|
| otherwise = And $ concat $ [map simplify dateqs, map simplify otherqs]
|
||||||
where (dateqs, otherqs) = partition queryIsDate $ filter (/=Any) qs
|
where (dateqs, otherqs) = partition queryIsDate $ filter (/=Any) qs
|
||||||
simplify (Or []) = Any
|
simplify (Or []) = Any
|
||||||
simplify (Or [q]) = simplifyQuery q
|
simplify (Or [q]) = simplifyQuery q
|
||||||
simplify (Or qs) | same qs = simplify $ head qs
|
simplify (Or qs) | same qs = simplify $ head qs
|
||||||
| any (==Any) qs = Any
|
| Any `elem` qs = Any
|
||||||
-- all queryIsDate qs = Date $ spansUnion $ mapMaybe queryTermDateSpan qs ?
|
-- all queryIsDate qs = Date $ spansUnion $ mapMaybe queryTermDateSpan qs ?
|
||||||
| otherwise = Or $ map simplify $ filter (/=None) qs
|
| otherwise = Or $ map simplify $ filter (/=None) qs
|
||||||
simplify (Date (DateSpan Nothing Nothing)) = Any
|
simplify (Date (DateSpan Nothing Nothing)) = Any
|
||||||
@ -445,8 +445,8 @@ queryIsStatus _ = False
|
|||||||
queryIsStartDateOnly :: Bool -> Query -> Bool
|
queryIsStartDateOnly :: Bool -> Query -> Bool
|
||||||
queryIsStartDateOnly _ Any = False
|
queryIsStartDateOnly _ Any = False
|
||||||
queryIsStartDateOnly _ None = False
|
queryIsStartDateOnly _ None = False
|
||||||
queryIsStartDateOnly secondary (Or ms) = and $ map (queryIsStartDateOnly secondary) ms
|
queryIsStartDateOnly secondary (Or ms) = all (queryIsStartDateOnly secondary) ms
|
||||||
queryIsStartDateOnly secondary (And ms) = and $ map (queryIsStartDateOnly secondary) ms
|
queryIsStartDateOnly secondary (And ms) = all (queryIsStartDateOnly secondary) ms
|
||||||
queryIsStartDateOnly False (Date (DateSpan (Just _) _)) = True
|
queryIsStartDateOnly False (Date (DateSpan (Just _) _)) = True
|
||||||
queryIsStartDateOnly True (Date2 (DateSpan (Just _) _)) = True
|
queryIsStartDateOnly True (Date2 (DateSpan (Just _) _)) = True
|
||||||
queryIsStartDateOnly _ _ = False
|
queryIsStartDateOnly _ _ = False
|
||||||
@ -613,7 +613,7 @@ matchesPosting (StatusQ s) p = postingStatus p == s
|
|||||||
matchesPosting (Real v) p = v == isReal p
|
matchesPosting (Real v) p = v == isReal p
|
||||||
matchesPosting q@(Depth _) Posting{paccount=a} = q `matchesAccount` a
|
matchesPosting q@(Depth _) Posting{paccount=a} = q `matchesAccount` a
|
||||||
matchesPosting q@(Amt _ _) Posting{pamount=as} = q `matchesMixedAmount` as
|
matchesPosting q@(Amt _ _) Posting{pamount=as} = q `matchesMixedAmount` as
|
||||||
matchesPosting (Sym r) Posting{pamount=as} = any (matchesCommodity (Sym r)) . map acommodity $ amountsRaw as
|
matchesPosting (Sym r) Posting{pamount=as} = any (matchesCommodity (Sym r) . acommodity) $ amountsRaw as
|
||||||
matchesPosting (Tag n v) p = case (reString n, v) of
|
matchesPosting (Tag n v) p = case (reString n, v) of
|
||||||
("payee", Just v) -> maybe False (regexMatchText v . transactionPayee) $ ptransaction p
|
("payee", Just v) -> maybe False (regexMatchText v . transactionPayee) $ ptransaction p
|
||||||
("note", Just v) -> maybe False (regexMatchText v . transactionNote) $ ptransaction p
|
("note", Just v) -> maybe False (regexMatchText v . transactionNote) $ ptransaction p
|
||||||
|
|||||||
@ -257,7 +257,7 @@ budgetReportAsTable
|
|||||||
|
|
||||||
addtotalrow
|
addtotalrow
|
||||||
| no_total_ = id
|
| no_total_ = id
|
||||||
| otherwise = let rh = Tab.Group NoLine $ map Header (replicate (length totalrows) "")
|
| otherwise = let rh = Tab.Group NoLine . replicate (length totalrows) $ Header ""
|
||||||
ch = Header [] -- ignored
|
ch = Header [] -- ignored
|
||||||
in (flip (concatTables SingleLine) $ Table rh ch totalrows)
|
in (flip (concatTables SingleLine) $ Table rh ch totalrows)
|
||||||
|
|
||||||
@ -279,7 +279,7 @@ budgetReportAsTable
|
|||||||
showntr = [showrow $ rowToBudgetCells tr]
|
showntr = [showrow $ rowToBudgetCells tr]
|
||||||
(trcs, trtexts) = unzip $ concat showntr
|
(trcs, trtexts) = unzip $ concat showntr
|
||||||
trwidths
|
trwidths
|
||||||
| transpose_ = snd $ splitAt (length texts) widths
|
| transpose_ = drop (length texts) widths
|
||||||
| otherwise = widths
|
| otherwise = widths
|
||||||
|
|
||||||
padcells = maybetranspose . fmap (fmap (uncurry paddisplaycell) . zip widths) . maybetranspose
|
padcells = maybetranspose . fmap (fmap (uncurry paddisplaycell) . zip widths) . maybetranspose
|
||||||
@ -334,7 +334,7 @@ budgetReportAsTable
|
|||||||
actualwidths = map (maximum' . map first3 ) $ cols
|
actualwidths = map (maximum' . map first3 ) $ cols
|
||||||
budgetwidths = map (maximum' . map second3) $ cols
|
budgetwidths = map (maximum' . map second3) $ cols
|
||||||
percentwidths = map (maximum' . map third3 ) $ cols
|
percentwidths = map (maximum' . map third3 ) $ cols
|
||||||
catcolumnwidths = foldl (\l a -> zipWith (++) l a) (repeat [])
|
catcolumnwidths = foldl' (zipWith (++)) $ repeat []
|
||||||
cols = maybetranspose $ catcolumnwidths $ map (cellswidth . rowToBudgetCells) items ++ [cellswidth $ rowToBudgetCells tr]
|
cols = maybetranspose $ catcolumnwidths $ map (cellswidth . rowToBudgetCells) items ++ [cellswidth $ rowToBudgetCells tr]
|
||||||
|
|
||||||
-- split a BudgetCell into BudgetDisplayCell's (one per commodity when applicable)
|
-- split a BudgetCell into BudgetDisplayCell's (one per commodity when applicable)
|
||||||
|
|||||||
@ -464,7 +464,7 @@ valuationTypeFromRawOpts rawopts = case (balancecalcopt rawopts, directcost, dir
|
|||||||
(CalcGain, NoCost, Nothing ) -> (directcost, Just $ AtEnd Nothing) -- If no valuation requested for gain, use AtEnd
|
(CalcGain, NoCost, Nothing ) -> (directcost, Just $ AtEnd Nothing) -- If no valuation requested for gain, use AtEnd
|
||||||
(_, _, _ ) -> (directcost, directval) -- Otherwise, use requested valuation
|
(_, _, _ ) -> (directcost, directval) -- Otherwise, use requested valuation
|
||||||
where
|
where
|
||||||
directcost = if any (== Cost) (map fst valuationopts) then Cost else NoCost
|
directcost = if Cost `elem` map fst valuationopts then Cost else NoCost
|
||||||
directval = lastMay $ mapMaybe snd valuationopts
|
directval = lastMay $ mapMaybe snd valuationopts
|
||||||
|
|
||||||
valuationopts = collectopts valuationfromrawopt rawopts
|
valuationopts = collectopts valuationfromrawopt rawopts
|
||||||
@ -551,9 +551,9 @@ mixedAmountApplyValuationAfterSumFromOptsWith :: ReportOpts -> Journal -> PriceO
|
|||||||
mixedAmountApplyValuationAfterSumFromOptsWith ropts j priceoracle =
|
mixedAmountApplyValuationAfterSumFromOptsWith ropts j priceoracle =
|
||||||
case valuationAfterSum ropts of
|
case valuationAfterSum ropts of
|
||||||
Just mc -> case balancecalc_ ropts of
|
Just mc -> case balancecalc_ ropts of
|
||||||
CalcGain -> \span -> gain mc span
|
CalcGain -> gain mc
|
||||||
_ -> \span -> valuation mc span . costing
|
_ -> \span -> valuation mc span . costing
|
||||||
Nothing -> \_span -> id
|
Nothing -> const id
|
||||||
where
|
where
|
||||||
valuation mc span = mixedAmountValueAtDate priceoracle styles mc (maybe err (addDays (-1)) $ spanEnd span)
|
valuation mc span = mixedAmountValueAtDate priceoracle styles mc (maybe err (addDays (-1)) $ spanEnd span)
|
||||||
gain mc span = mixedAmountGainAtDate priceoracle styles mc (maybe err (addDays (-1)) $ spanEnd span)
|
gain mc span = mixedAmountGainAtDate priceoracle styles mc (maybe err (addDays (-1)) $ spanEnd span)
|
||||||
|
|||||||
@ -677,7 +677,7 @@ balanceReportAsTable opts@ReportOpts{average_, row_total_, balanceaccum_}
|
|||||||
| no_total_ opts = id
|
| no_total_ opts = id
|
||||||
| otherwise =
|
| otherwise =
|
||||||
let totalrows = multiBalanceRowAsTableText opts tr
|
let totalrows = multiBalanceRowAsTableText opts tr
|
||||||
rh = Tab.Group NoLine $ map Header (replicate (length totalrows) "")
|
rh = Tab.Group NoLine . replicate (length totalrows) $ Header ""
|
||||||
ch = Header [] -- ignored
|
ch = Header [] -- ignored
|
||||||
in (flip (concatTables SingleLine) $ Table rh ch totalrows)
|
in (flip (concatTables SingleLine) $ Table rh ch totalrows)
|
||||||
maybetranspose | transpose_ opts = \(Table rh ch vals) -> Table ch rh (transpose vals)
|
maybetranspose | transpose_ opts = \(Table rh ch vals) -> Table ch rh (transpose vals)
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user