Skip to content

Commit

Permalink
refactor: lib: hlint cleanups
Browse files Browse the repository at this point in the history
  • Loading branch information
simonmichael committed Feb 14, 2019
1 parent 0387705 commit bc7a147
Show file tree
Hide file tree
Showing 14 changed files with 579 additions and 472 deletions.
3 changes: 2 additions & 1 deletion .hlint.yaml
Expand Up @@ -47,10 +47,11 @@
# - ignore: {name: Use let} # - ignore: {name: Use let}
# - ignore: {name: Use const, within: SpecialModule} # Only within certain modules # - ignore: {name: Use const, within: SpecialModule} # Only within certain modules


- ignore: {name: Use camelCase} - ignore: {name: Reduce duplication}
- ignore: {name: Redundant $} - ignore: {name: Redundant $}
- ignore: {name: Redundant bracket} - ignore: {name: Redundant bracket}
- ignore: {name: Redundant do} - ignore: {name: Redundant do}
- ignore: {name: Use camelCase}




# Define some custom infix operators # Define some custom infix operators
Expand Down
2 changes: 1 addition & 1 deletion hledger-lib/Hledger/Data/Account.hs
Expand Up @@ -242,7 +242,7 @@ sortAccountTreeByDeclaration :: Account -> Account
sortAccountTreeByDeclaration a sortAccountTreeByDeclaration a
| null $ asubs a = a | null $ asubs a = a
| otherwise = a{asubs= | otherwise = a{asubs=
sortBy (comparing accountDeclarationOrderAndName) $ sortOn accountDeclarationOrderAndName $
map sortAccountTreeByDeclaration $ asubs a map sortAccountTreeByDeclaration $ asubs a
} }


Expand Down
3 changes: 1 addition & 2 deletions hledger-lib/Hledger/Data/Amount.hs
Expand Up @@ -132,7 +132,6 @@ import Data.List
import Data.Map (findWithDefault) import Data.Map (findWithDefault)
import Data.Maybe import Data.Maybe
import Data.Time.Calendar (Day) import Data.Time.Calendar (Day)
import Data.Ord (comparing)
-- import Data.Text (Text) -- import Data.Text (Text)
import qualified Data.Text as T import qualified Data.Text as T
import Safe (maximumDef) import Safe (maximumDef)
Expand Down Expand Up @@ -469,7 +468,7 @@ commodityValue j valuationdate c
where where
dbg = dbg8 ("using market price for "++T.unpack c) dbg = dbg8 ("using market price for "++T.unpack c)
applicableprices = applicableprices =
[p | p <- sortBy (comparing mpdate) $ jmarketprices j [p | p <- sortOn mpdate $ jmarketprices j
, mpcommodity p == c , mpcommodity p == c
, mpdate p <= valuationdate , mpdate p <= valuationdate
] ]
Expand Down
2 changes: 1 addition & 1 deletion hledger-lib/Hledger/Data/Commodity.hs
Expand Up @@ -26,7 +26,7 @@ import Hledger.Utils




-- characters that may not be used in a non-quoted commodity symbol -- characters that may not be used in a non-quoted commodity symbol
nonsimplecommoditychars = "0123456789-+.@*;\n \"{}=" :: [Char] nonsimplecommoditychars = "0123456789-+.@*;\n \"{}=" :: String


isNonsimpleCommodityChar :: Char -> Bool isNonsimpleCommodityChar :: Char -> Bool
isNonsimpleCommodityChar c = isDigit c || c `textElem` otherChars isNonsimpleCommodityChar c = isDigit c || c `textElem` otherChars
Expand Down
93 changes: 41 additions & 52 deletions hledger-lib/Hledger/Data/Dates.hs
Expand Up @@ -126,21 +126,15 @@ showDateSpanMonthAbbrev = showPeriodMonthAbbrev . dateSpanAsPeriod


-- | Get the current local date. -- | Get the current local date.
getCurrentDay :: IO Day getCurrentDay :: IO Day
getCurrentDay = do getCurrentDay = localDay . zonedTimeToLocalTime <$> getZonedTime
t <- getZonedTime
return $ localDay (zonedTimeToLocalTime t)


-- | Get the current local month number. -- | Get the current local month number.
getCurrentMonth :: IO Int getCurrentMonth :: IO Int
getCurrentMonth = do getCurrentMonth = second3 . toGregorian <$> getCurrentDay
(_,m,_) <- toGregorian `fmap` getCurrentDay
return m


-- | Get the current local year. -- | Get the current local year.
getCurrentYear :: IO Integer getCurrentYear :: IO Integer
getCurrentYear = do getCurrentYear = first3 . toGregorian <$> getCurrentDay
(y,_,_) <- toGregorian `fmap` getCurrentDay
return y


elapsedSeconds :: Fractional a => UTCTime -> UTCTime -> a elapsedSeconds :: Fractional a => UTCTime -> UTCTime -> a
elapsedSeconds t1 = realToFrac . diffUTCTime t1 elapsedSeconds t1 = realToFrac . diffUTCTime t1
Expand Down Expand Up @@ -380,14 +374,13 @@ spanFromSmartDate refdate sdate = DateSpan (Just b) (Just e)
-- | Convert a smart date string to an explicit yyyy\/mm\/dd string using -- | Convert a smart date string to an explicit yyyy\/mm\/dd string using
-- the provided reference date, or raise an error. -- the provided reference date, or raise an error.
fixSmartDateStr :: Day -> Text -> String fixSmartDateStr :: Day -> Text -> String
fixSmartDateStr d s = either fixSmartDateStr d s =
(\e->error' $ printf "could not parse date %s %s" (show s) (show e)) either (error' . printf "could not parse date %s %s" (show s) . show) id $
id (fixSmartDateStrEither d s :: Either (ParseErrorBundle Text CustomErr) String)
$ (fixSmartDateStrEither d s :: Either (ParseErrorBundle Text CustomErr) String)


-- | A safe version of fixSmartDateStr. -- | A safe version of fixSmartDateStr.
fixSmartDateStrEither :: Day -> Text -> Either (ParseErrorBundle Text CustomErr) String fixSmartDateStrEither :: Day -> Text -> Either (ParseErrorBundle Text CustomErr) String
fixSmartDateStrEither d = either Left (Right . showDate) . fixSmartDateStrEither' d fixSmartDateStrEither d = fmap showDate . fixSmartDateStrEither' d


fixSmartDateStrEither' fixSmartDateStrEither'
:: Day -> Text -> Either (ParseErrorBundle Text CustomErr) Day :: Day -> Text -> Either (ParseErrorBundle Text CustomErr) Day
Expand Down Expand Up @@ -469,34 +462,34 @@ fixSmartDateStrEither' d s = case parsewith smartdateonly (T.toLower s) of
-- "2009/01/01" -- "2009/01/01"
-- --
fixSmartDate :: Day -> SmartDate -> Day fixSmartDate :: Day -> SmartDate -> Day
fixSmartDate refdate sdate = fix sdate fixSmartDate refdate = fix
where where
fix :: SmartDate -> Day fix :: SmartDate -> Day
fix ("","","today") = fromGregorian ry rm rd fix ("", "", "today") = fromGregorian ry rm rd
fix ("","this","day") = fromGregorian ry rm rd fix ("", "this", "day") = fromGregorian ry rm rd
fix ("","","yesterday") = prevday refdate fix ("", "", "yesterday") = prevday refdate
fix ("","last","day") = prevday refdate fix ("", "last", "day") = prevday refdate
fix ("","","tomorrow") = nextday refdate fix ("", "", "tomorrow") = nextday refdate
fix ("","next","day") = nextday refdate fix ("", "next", "day") = nextday refdate
fix ("","last","week") = prevweek refdate fix ("", "last", "week") = prevweek refdate
fix ("","this","week") = thisweek refdate fix ("", "this", "week") = thisweek refdate
fix ("","next","week") = nextweek refdate fix ("", "next", "week") = nextweek refdate
fix ("","last","month") = prevmonth refdate fix ("", "last", "month") = prevmonth refdate
fix ("","this","month") = thismonth refdate fix ("", "this", "month") = thismonth refdate
fix ("","next","month") = nextmonth refdate fix ("", "next", "month") = nextmonth refdate
fix ("","last","quarter") = prevquarter refdate fix ("", "last", "quarter") = prevquarter refdate
fix ("","this","quarter") = thisquarter refdate fix ("", "this", "quarter") = thisquarter refdate
fix ("","next","quarter") = nextquarter refdate fix ("", "next", "quarter") = nextquarter refdate
fix ("","last","year") = prevyear refdate fix ("", "last", "year") = prevyear refdate
fix ("","this","year") = thisyear refdate fix ("", "this", "year") = thisyear refdate
fix ("","next","year") = nextyear refdate fix ("", "next", "year") = nextyear refdate
fix ("","",d) = fromGregorian ry rm (read d) fix ("", "", d) = fromGregorian ry rm (read d)
fix ("",m,"") = fromGregorian ry (read m) 1 fix ("", m, "") = fromGregorian ry (read m) 1
fix ("",m,d) = fromGregorian ry (read m) (read d) fix ("", m, d) = fromGregorian ry (read m) (read d)
fix (y,"","") = fromGregorian (read y) 1 1 fix (y, "", "") = fromGregorian (read y) 1 1
fix (y,m,"") = fromGregorian (read y) (read m) 1 fix (y, m, "") = fromGregorian (read y) (read m) 1
fix (y,m,d) = fromGregorian (read y) (read m) (read d) fix (y, m, d) = fromGregorian (read y) (read m) (read d)
(ry,rm,rd) = toGregorian refdate (ry, rm, rd) = toGregorian refdate


prevday :: Day -> Day prevday :: Day -> Day
prevday = addDays (-1) prevday = addDays (-1)
Expand Down Expand Up @@ -764,7 +757,7 @@ smartdateonly = do
eof eof
return d return d


datesepchars :: [Char] datesepchars :: String
datesepchars = "/-." datesepchars = "/-."


datesepchar :: TextParser m Char datesepchar :: TextParser m Char
Expand Down Expand Up @@ -980,8 +973,7 @@ reportingintervalp = choice' [
return $ DayOfWeek n, return $ DayOfWeek n,
do string' "every" do string' "every"
skipMany spacenonewline skipMany spacenonewline
n <- weekday DayOfWeek <$> weekday,
return $ DayOfWeek n,
do string' "every" do string' "every"
skipMany spacenonewline skipMany spacenonewline
n <- nth n <- nth
Expand Down Expand Up @@ -1034,7 +1026,7 @@ reportingintervalp = choice' [
return $ intcons 1, return $ intcons 1,
do string' "every" do string' "every"
skipMany spacenonewline skipMany spacenonewline
n <- fmap read $ some digitChar n <- read <$> some digitChar
skipMany spacenonewline skipMany spacenonewline
string' plural' string' plural'
return $ intcons n return $ intcons n
Expand All @@ -1061,8 +1053,7 @@ doubledatespanp rdate = do
b <- smartdate b <- smartdate
skipMany spacenonewline skipMany spacenonewline
optional (choice [string' "to", string' "-"] >> skipMany spacenonewline) optional (choice [string' "to", string' "-"] >> skipMany spacenonewline)
e <- smartdate DateSpan (Just $ fixSmartDate rdate b) . Just . fixSmartDate rdate <$> smartdate
return $ DateSpan (Just $ fixSmartDate rdate b) (Just $ fixSmartDate rdate e)


fromdatespanp :: Day -> TextParser m DateSpan fromdatespanp :: Day -> TextParser m DateSpan
fromdatespanp rdate = do fromdatespanp rdate = do
Expand All @@ -1081,14 +1072,12 @@ fromdatespanp rdate = do
todatespanp :: Day -> TextParser m DateSpan todatespanp :: Day -> TextParser m DateSpan
todatespanp rdate = do todatespanp rdate = do
choice [string' "to", string' "-"] >> skipMany spacenonewline choice [string' "to", string' "-"] >> skipMany spacenonewline
e <- smartdate DateSpan Nothing . Just . fixSmartDate rdate <$> smartdate
return $ DateSpan Nothing (Just $ fixSmartDate rdate e)


justdatespanp :: Day -> TextParser m DateSpan justdatespanp :: Day -> TextParser m DateSpan
justdatespanp rdate = do justdatespanp rdate = do
optional (string' "in" >> skipMany spacenonewline) optional (string' "in" >> skipMany spacenonewline)
d <- smartdate spanFromSmartDate rdate <$> smartdate
return $ spanFromSmartDate rdate d


-- | Make a datespan from two valid date strings parseable by parsedate -- | Make a datespan from two valid date strings parseable by parsedate
-- (or raise an error). Eg: mkdatespan \"2011/1/1\" \"2011/12/31\". -- (or raise an error). Eg: mkdatespan \"2011/1/1\" \"2011/12/31\".
Expand Down
58 changes: 28 additions & 30 deletions hledger-lib/Hledger/Data/Journal.hs
Expand Up @@ -90,7 +90,6 @@ import Data.Maybe
#if !(MIN_VERSION_base(4,11,0)) #if !(MIN_VERSION_base(4,11,0))
import Data.Monoid import Data.Monoid
#endif #endif
import Data.Ord
import qualified Data.Semigroup as Sem import qualified Data.Semigroup as Sem
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as T import qualified Data.Text as T
Expand Down Expand Up @@ -672,7 +671,7 @@ journalBalanceTransactionsST assrt j createStore storeIn extract =
(Just $ journalCommodityStyles j) (Just $ journalCommodityStyles j)
(getModifierAccountNames j) (getModifierAccountNames j)
flip R.runReaderT env $ do flip R.runReaderT env $ do
dated <- fmap snd . sortBy (comparing fst) . concat dated <- fmap snd . sortOn fst . concat
<$> mapM' discriminateByDate (jtxns j) <$> mapM' discriminateByDate (jtxns j)
mapM' checkInferAndRegisterAmounts dated mapM' checkInferAndRegisterAmounts dated
lift $ extract txStore lift $ extract txStore
Expand Down Expand Up @@ -714,33 +713,33 @@ discriminateByDate :: Transaction
-> CurrentBalancesModifier s [(Day, Either Posting Transaction)] -> CurrentBalancesModifier s [(Day, Either Posting Transaction)]
discriminateByDate tx discriminateByDate tx
| null (assignmentPostings tx) = do | null (assignmentPostings tx) = do
styles <- R.reader $ eStyles styles <- R.reader $ eStyles
balanced <- lift $ ExceptT $ return $ balanceTransaction styles tx balanced <- lift $ ExceptT $ return $ balanceTransaction styles tx
storeTransaction balanced storeTransaction balanced
return $ return $ fmap (postingDate &&& (Left . removePrices)) $ tpostings $ balanced
fmap (postingDate &&& (Left . removePrices)) $ tpostings $ balanced | otherwise = do
| True = do when (any (isJust . pdate) $ tpostings tx) $
when (any (isJust . pdate) $ tpostings tx) $ throwError $
throwError $ unlines $ unlines $
["postings may not have both a custom date and a balance assignment." [ "postings may not have both a custom date and a balance assignment."
,"Write the posting amount explicitly, or remove the posting date:\n" , "Write the posting amount explicitly, or remove the posting date:\n"
, showTransaction tx] , showTransaction tx
return ]
[(tdate tx, Right $ tx { tpostings = removePrices <$> tpostings tx })] return [(tdate tx, Right $ tx {tpostings = removePrices <$> tpostings tx})]


-- | Throw an error if a posting is in the unassignable set. -- | Throw an error if a posting is in the unassignable set.
checkUnassignablePosting :: Posting -> CurrentBalancesModifier s () checkUnassignablePosting :: Posting -> CurrentBalancesModifier s ()
checkUnassignablePosting p = do checkUnassignablePosting p = do
unassignable <- R.asks eUnassignable unassignable <- R.asks eUnassignable
if (isAssignment p && paccount p `S.member` unassignable) when (isAssignment p && paccount p `S.member` unassignable) $
then throwError $ unlines $ throwError $
[ "cannot assign amount to account " unlines $
, "" [ "cannot assign amount to account "
, " " ++ (T.unpack $ paccount p) , ""
, "" , " " ++ T.unpack (paccount p)
, "because it is also included in transaction modifiers." , ""
] , "because it is also included in transaction modifiers."
else return () ]




-- | This function takes an object describing changes to -- | This function takes an object describing changes to
Expand Down Expand Up @@ -789,7 +788,7 @@ checkInferAndRegisterAmounts (Right oldTx) = do
Just ba | baexact ba -> do Just ba | baexact ba -> do
diff <- setMixedBalance acc $ Mixed [baamount ba] diff <- setMixedBalance acc $ Mixed [baamount ba]
fullPosting diff p fullPosting diff p
Just ba | otherwise -> do Just ba -> do
old <- liftModifier $ \Env{ eBalances = bals } -> HT.lookup bals acc old <- liftModifier $ \Env{ eBalances = bals } -> HT.lookup bals acc
let amt = baamount ba let amt = baamount ba
assertedcomm = acommodity amt assertedcomm = acommodity amt
Expand Down Expand Up @@ -884,13 +883,12 @@ commodityStylesFromAmounts amts = M.fromList commstyles
-- That is: the style of the first, and the maximum precision of all. -- That is: the style of the first, and the maximum precision of all.
canonicalStyleFrom :: [AmountStyle] -> AmountStyle canonicalStyleFrom :: [AmountStyle] -> AmountStyle
canonicalStyleFrom [] = amountstyle canonicalStyleFrom [] = amountstyle
canonicalStyleFrom ss@(first:_) = canonicalStyleFrom ss@(first:_) = first {asprecision = prec, asdecimalpoint = mdec, asdigitgroups = mgrps}
first{asprecision=prec, asdecimalpoint=mdec, asdigitgroups=mgrps}
where where
mgrps = maybe Nothing Just $ headMay $ catMaybes $ map asdigitgroups ss mgrps = headMay $ mapMaybe asdigitgroups ss
-- precision is maximum of all precisions -- precision is maximum of all precisions
prec = maximumStrict $ map asprecision ss prec = maximumStrict $ map asprecision ss
mdec = Just $ headDef '.' $ catMaybes $ map asdecimalpoint ss mdec = Just $ headDef '.' $ mapMaybe asdecimalpoint ss
-- precision is that of first amount with a decimal point -- precision is that of first amount with a decimal point
-- (mdec, prec) = -- (mdec, prec) =
-- case filter (isJust . asdecimalpoint) ss of -- case filter (isJust . asdecimalpoint) ss of
Expand Down Expand Up @@ -993,7 +991,7 @@ journalDateSpan secondary j
latest = maximumStrict dates latest = maximumStrict dates
dates = pdates ++ tdates dates = pdates ++ tdates
tdates = map (if secondary then transactionDate2 else tdate) ts tdates = map (if secondary then transactionDate2 else tdate) ts
pdates = concatMap (catMaybes . map (if secondary then (Just . postingDate2) else pdate) . tpostings) ts pdates = concatMap (mapMaybe (if secondary then (Just . postingDate2) else pdate) . tpostings) ts
ts = jtxns j ts = jtxns j


-- | Apply the pivot transformation to all postings in a journal, -- | Apply the pivot transformation to all postings in a journal,
Expand Down
19 changes: 10 additions & 9 deletions hledger-lib/Hledger/Data/Ledger.hs
Expand Up @@ -107,12 +107,13 @@ ledgerCommodities = M.keys . jinferredcommodities . ljournal


-- tests -- tests


tests_Ledger = tests "Ledger" [ tests_Ledger =

tests
tests "ledgerFromJournal" [ "Ledger"
(length $ ledgerPostings $ ledgerFromJournal Any nulljournal) `is` 0 [ tests
,(length $ ledgerPostings $ ledgerFromJournal Any samplejournal) `is` 13 "ledgerFromJournal"
,(length $ ledgerPostings $ ledgerFromJournal (Depth 2) samplejournal) `is` 7 [ length (ledgerPostings $ ledgerFromJournal Any nulljournal) `is` 0
] , length (ledgerPostings $ ledgerFromJournal Any samplejournal) `is` 13

, length (ledgerPostings $ ledgerFromJournal (Depth 2) samplejournal) `is` 7
] ]
]
2 changes: 0 additions & 2 deletions hledger-lib/Hledger/Data/MarketPrice.hs
Expand Up @@ -8,8 +8,6 @@ value of things at a given date.
-} -}


{-# LANGUAGE OverloadedStrings, LambdaCase #-}

module Hledger.Data.MarketPrice module Hledger.Data.MarketPrice
where where
import qualified Data.Text as T import qualified Data.Text as T
Expand Down
1 change: 0 additions & 1 deletion hledger-lib/Hledger/Data/PeriodicTransaction.hs
@@ -1,7 +1,6 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StandaloneDeriving #-}
{-| {-|
A 'PeriodicTransaction' is a rule describing recurring transactions. A 'PeriodicTransaction' is a rule describing recurring transactions.
Expand Down
7 changes: 3 additions & 4 deletions hledger-lib/Hledger/Data/Posting.hs
Expand Up @@ -66,7 +66,6 @@ import Data.MemoUgly (memo)
#if !(MIN_VERSION_base(4,11,0)) #if !(MIN_VERSION_base(4,11,0))
import Data.Monoid import Data.Monoid
#endif #endif
import Data.Ord
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as T import qualified Data.Text as T
import Data.Time.Calendar import Data.Time.Calendar
Expand Down Expand Up @@ -176,7 +175,7 @@ postingDate2 p = headDef nulldate $ catMaybes dates
where dates = [pdate2 p where dates = [pdate2 p
,maybe Nothing tdate2 $ ptransaction p ,maybe Nothing tdate2 $ ptransaction p
,pdate p ,pdate p
,maybe Nothing (Just . tdate) $ ptransaction p ,fmap tdate (ptransaction p)
] ]


-- | Get a posting's status. This is cleared or pending if those are -- | Get a posting's status. This is cleared or pending if those are
Expand Down Expand Up @@ -237,14 +236,14 @@ isEmptyPosting = isZeroMixedAmount . pamount
postingsDateSpan :: [Posting] -> DateSpan postingsDateSpan :: [Posting] -> DateSpan
postingsDateSpan [] = DateSpan Nothing Nothing postingsDateSpan [] = DateSpan Nothing Nothing
postingsDateSpan ps = DateSpan (Just $ postingDate $ head ps') (Just $ addDays 1 $ postingDate $ last ps') postingsDateSpan ps = DateSpan (Just $ postingDate $ head ps') (Just $ addDays 1 $ postingDate $ last ps')
where ps' = sortBy (comparing postingDate) ps where ps' = sortOn postingDate ps


-- --date2-sensitive version, as above. -- --date2-sensitive version, as above.
postingsDateSpan' :: WhichDate -> [Posting] -> DateSpan postingsDateSpan' :: WhichDate -> [Posting] -> DateSpan
postingsDateSpan' _ [] = DateSpan Nothing Nothing postingsDateSpan' _ [] = DateSpan Nothing Nothing
postingsDateSpan' wd ps = DateSpan (Just $ postingdate $ head ps') (Just $ addDays 1 $ postingdate $ last ps') postingsDateSpan' wd ps = DateSpan (Just $ postingdate $ head ps') (Just $ addDays 1 $ postingdate $ last ps')
where where
ps' = sortBy (comparing postingdate) ps ps' = sortOn postingdate ps
postingdate = if wd == PrimaryDate then postingDate else postingDate2 postingdate = if wd == PrimaryDate then postingDate else postingDate2


-- AccountName stuff that depends on PostingType -- AccountName stuff that depends on PostingType
Expand Down

0 comments on commit bc7a147

Please sign in to comment.