lib: Account, AccountName: hlint

This commit is contained in:
Simon Michael 2018-02-15 11:38:34 -08:00
parent 6d94eed6fd
commit b231d99e38
2 changed files with 7 additions and 7 deletions

View File

@ -1,4 +1,4 @@
{-# LANGUAGE RecordWildCards, StandaloneDeriving, OverloadedStrings #-} {-# LANGUAGE RecordWildCards, OverloadedStrings #-}
{-| {-|
@ -93,7 +93,7 @@ tieAccountParents = tie Nothing
-- | Look up an account's numeric code, if any, from the Journal and set it. -- | Look up an account's numeric code, if any, from the Journal and set it.
accountSetCodeFrom :: Journal -> Account -> Account accountSetCodeFrom :: Journal -> Account -> Account
accountSetCodeFrom j a = a{acode=fromMaybe Nothing $ (lookup (aname a) $ jaccounts j)} accountSetCodeFrom j a = a{acode=fromMaybe Nothing $ lookup (aname a) (jaccounts j)}
-- | Get this account's parent accounts, from the nearest up to the root. -- | Get this account's parent accounts, from the nearest up to the root.
parentAccounts :: Account -> [Account] parentAccounts :: Account -> [Account]
@ -200,7 +200,7 @@ sortAccountTreeByAmount :: NormalSign -> Account -> Account
sortAccountTreeByAmount normalsign a sortAccountTreeByAmount normalsign a
| null $ asubs a = a | null $ asubs a = a
| otherwise = a{asubs= | otherwise = a{asubs=
sortBy (maybeflip $ comparing aibalance) $ sortBy (maybeflip $ comparing aibalance) $
map (sortAccountTreeByAmount normalsign) $ asubs a} map (sortAccountTreeByAmount normalsign) $ asubs a}
where where
maybeflip | normalsign==NormallyNegative = id maybeflip | normalsign==NormallyNegative = id

View File

@ -43,7 +43,7 @@ accountLeafName = last . accountNameComponents
accountSummarisedName :: AccountName -> Text accountSummarisedName :: AccountName -> Text
accountSummarisedName a accountSummarisedName a
-- length cs > 1 = take 2 (head cs) ++ ":" ++ a' -- length cs > 1 = take 2 (head cs) ++ ":" ++ a'
| length cs > 1 = (T.intercalate ":" (map (T.take 2) $ init cs)) <> ":" <> a' | length cs > 1 = T.intercalate ":" (map (T.take 2) $ init cs) <> ":" <> a'
| otherwise = a' | otherwise = a'
where where
cs = accountNameComponents a cs = accountNameComponents a
@ -125,11 +125,11 @@ elideAccountName width s
| " (split)" `T.isSuffixOf` s = | " (split)" `T.isSuffixOf` s =
let let
names = T.splitOn ", " $ T.take (T.length s - 8) s names = T.splitOn ", " $ T.take (T.length s - 8) s
widthpername = (max 0 (width - 8 - 2 * (max 1 (length names) - 1))) `div` length names widthpername = max 0 (width - 8 - 2 * (max 1 (length names) - 1)) `div` length names
in in
fitText Nothing (Just width) True False $ fitText Nothing (Just width) True False $
(<>" (split)") $ (<>" (split)") $
T.intercalate ", " $ T.intercalate ", "
[accountNameFromComponents $ elideparts widthpername [] $ accountNameComponents s' | s' <- names] [accountNameFromComponents $ elideparts widthpername [] $ accountNameComponents s' | s' <- names]
| otherwise = | otherwise =
fitText Nothing (Just width) True False $ accountNameFromComponents $ elideparts width [] $ accountNameComponents s fitText Nothing (Just width) True False $ accountNameFromComponents $ elideparts width [] $ accountNameComponents s
@ -174,7 +174,7 @@ accountRegexToAccountName = T.pack . regexReplace "^\\^(.*?)\\(:\\|\\$\\)$" "\\1
-- | Does this string look like an exact account-matching regular expression ? -- | Does this string look like an exact account-matching regular expression ?
isAccountRegex :: String -> Bool isAccountRegex :: String -> Bool
isAccountRegex s = take 1 s == "^" && (take 5 $ reverse s) == ")$|:(" isAccountRegex s = take 1 s == "^" && take 5 (reverse s) == ")$|:("
tests_Hledger_Data_AccountName = TestList tests_Hledger_Data_AccountName = TestList
[ [