rename FormatString to OutputFormat
It was going to be Format, but that clashes with file format. Press on.
This commit is contained in:
parent
6f49263c9b
commit
dd2f293094
@ -1,8 +1,8 @@
|
|||||||
module Hledger.Data.FormatStrings (
|
module Hledger.Data.OutputFormat (
|
||||||
parseFormatString
|
parseStringFormat
|
||||||
, formatStrings
|
, formatsp
|
||||||
, formatValue
|
, formatValue
|
||||||
, FormatString(..)
|
, OutputFormat(..)
|
||||||
, HledgerFormatField(..)
|
, HledgerFormatField(..)
|
||||||
, tests
|
, tests
|
||||||
) where
|
) where
|
||||||
@ -25,8 +25,8 @@ formatValue leftJustified min max value = printf formatS value
|
|||||||
max' = maybe "" (\i -> "." ++ (show i)) max
|
max' = maybe "" (\i -> "." ++ (show i)) max
|
||||||
formatS = "%" ++ l ++ min' ++ max' ++ "s"
|
formatS = "%" ++ l ++ min' ++ max' ++ "s"
|
||||||
|
|
||||||
parseFormatString :: String -> Either String [FormatString]
|
parseStringFormat :: String -> Either String [OutputFormat]
|
||||||
parseFormatString input = case (runParser formatStrings () "(unknown)") input of
|
parseStringFormat input = case (runParser formatsp () "(unknown)") input of
|
||||||
Left y -> Left $ show y
|
Left y -> Left $ show y
|
||||||
Right x -> Right x
|
Right x -> Right x
|
||||||
|
|
||||||
@ -43,7 +43,7 @@ field = do
|
|||||||
<|> try (string "total" >> return TotalField)
|
<|> try (string "total" >> return TotalField)
|
||||||
<|> try (many1 digit >>= (\s -> return $ FieldNo $ read s))
|
<|> try (many1 digit >>= (\s -> return $ FieldNo $ read s))
|
||||||
|
|
||||||
formatField :: GenParser Char st FormatString
|
formatField :: GenParser Char st OutputFormat
|
||||||
formatField = do
|
formatField = do
|
||||||
char '%'
|
char '%'
|
||||||
leftJustified <- optionMaybe (char '-')
|
leftJustified <- optionMaybe (char '-')
|
||||||
@ -58,7 +58,7 @@ formatField = do
|
|||||||
Just text -> Just m where ((m,_):_) = readDec text
|
Just text -> Just m where ((m,_):_) = readDec text
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
|
|
||||||
formatLiteral :: GenParser Char st FormatString
|
formatLiteral :: GenParser Char st OutputFormat
|
||||||
formatLiteral = do
|
formatLiteral = do
|
||||||
s <- many1 c
|
s <- many1 c
|
||||||
return $ FormatLiteral s
|
return $ FormatLiteral s
|
||||||
@ -67,23 +67,23 @@ formatLiteral = do
|
|||||||
c = (satisfy isPrintableButNotPercentage <?> "printable character")
|
c = (satisfy isPrintableButNotPercentage <?> "printable character")
|
||||||
<|> try (string "%%" >> return '%')
|
<|> try (string "%%" >> return '%')
|
||||||
|
|
||||||
formatStr :: GenParser Char st FormatString
|
formatp :: GenParser Char st OutputFormat
|
||||||
formatStr =
|
formatp =
|
||||||
formatField
|
formatField
|
||||||
<|> formatLiteral
|
<|> formatLiteral
|
||||||
|
|
||||||
formatStrings :: GenParser Char st [FormatString]
|
formatsp :: GenParser Char st [OutputFormat]
|
||||||
formatStrings = many formatStr
|
formatsp = many formatp
|
||||||
|
|
||||||
testFormat :: FormatString -> String -> String -> Assertion
|
testFormat :: OutputFormat -> String -> String -> Assertion
|
||||||
testFormat fs value expected = assertEqual name expected actual
|
testFormat fs value expected = assertEqual name expected actual
|
||||||
where
|
where
|
||||||
(name, actual) = case fs of
|
(name, actual) = case fs of
|
||||||
FormatLiteral l -> ("literal", formatValue False Nothing Nothing l)
|
FormatLiteral l -> ("literal", formatValue False Nothing Nothing l)
|
||||||
FormatField leftJustify min max _ -> ("field", formatValue leftJustify min max value)
|
FormatField leftJustify min max _ -> ("field", formatValue leftJustify min max value)
|
||||||
|
|
||||||
testParser :: String -> [FormatString] -> Assertion
|
testParser :: String -> [OutputFormat] -> Assertion
|
||||||
testParser s expected = case (parseFormatString s) of
|
testParser s expected = case (parseStringFormat s) of
|
||||||
Left error -> assertFailure $ show error
|
Left error -> assertFailure $ show error
|
||||||
Right actual -> assertEqual ("Input: " ++ s) expected actual
|
Right actual -> assertEqual ("Input: " ++ s) expected actual
|
||||||
|
|
||||||
@ -195,7 +195,7 @@ data HledgerFormatField =
|
|||||||
| FieldNo Int
|
| FieldNo Int
|
||||||
deriving (Show, Eq)
|
deriving (Show, Eq)
|
||||||
|
|
||||||
data FormatString =
|
data OutputFormat =
|
||||||
FormatLiteral String
|
FormatLiteral String
|
||||||
| FormatField Bool -- Left justified ?
|
| FormatField Bool -- Left justified ?
|
||||||
(Maybe Int) -- Min width
|
(Maybe Int) -- Min width
|
||||||
|
|||||||
@ -39,7 +39,7 @@ library
|
|||||||
Hledger.Data.Amount
|
Hledger.Data.Amount
|
||||||
Hledger.Data.Commodity
|
Hledger.Data.Commodity
|
||||||
Hledger.Data.Dates
|
Hledger.Data.Dates
|
||||||
Hledger.Data.FormatStrings
|
Hledger.Data.OutputFormat
|
||||||
Hledger.Data.Journal
|
Hledger.Data.Journal
|
||||||
Hledger.Data.Ledger
|
Hledger.Data.Ledger
|
||||||
Hledger.Data.Posting
|
Hledger.Data.Posting
|
||||||
|
|||||||
@ -250,7 +250,7 @@ import Text.Tabular.AsciiArt
|
|||||||
import Hledger
|
import Hledger
|
||||||
import Prelude hiding (putStr)
|
import Prelude hiding (putStr)
|
||||||
import Hledger.Utils.UTF8IOCompat (putStr)
|
import Hledger.Utils.UTF8IOCompat (putStr)
|
||||||
import Hledger.Data.FormatStrings
|
import Hledger.Data.OutputFormat
|
||||||
import Hledger.Cli.Options
|
import Hledger.Cli.Options
|
||||||
|
|
||||||
|
|
||||||
@ -309,7 +309,7 @@ This implementation turned out to be a bit convoluted but implements the followi
|
|||||||
b USD -1 ; Account 'b' has two amounts. The account name is printed on the last line.
|
b USD -1 ; Account 'b' has two amounts. The account name is printed on the last line.
|
||||||
-}
|
-}
|
||||||
-- | Render one balance report line item as plain text suitable for console output.
|
-- | Render one balance report line item as plain text suitable for console output.
|
||||||
balanceReportItemAsText :: ReportOpts -> [FormatString] -> BalanceReportItem -> [String]
|
balanceReportItemAsText :: ReportOpts -> [OutputFormat] -> BalanceReportItem -> [String]
|
||||||
balanceReportItemAsText opts format (_, accountName, depth, Mixed amounts) =
|
balanceReportItemAsText opts format (_, accountName, depth, Mixed amounts) =
|
||||||
-- 'amounts' could contain several quantities of the same commodity with different price.
|
-- 'amounts' could contain several quantities of the same commodity with different price.
|
||||||
-- In order to combine them into single value (which is expected) we take the first price and
|
-- In order to combine them into single value (which is expected) we take the first price and
|
||||||
@ -325,7 +325,7 @@ balanceReportItemAsText opts format (_, accountName, depth, Mixed amounts) =
|
|||||||
multiline [a] = [formatBalanceReportItem opts (Just accountName) depth a format]
|
multiline [a] = [formatBalanceReportItem opts (Just accountName) depth a format]
|
||||||
multiline (a:as) = (formatBalanceReportItem opts Nothing depth a format) : multiline as
|
multiline (a:as) = (formatBalanceReportItem opts Nothing depth a format) : multiline as
|
||||||
|
|
||||||
formatBalanceReportItem :: ReportOpts -> Maybe AccountName -> Int -> Amount -> [FormatString] -> String
|
formatBalanceReportItem :: ReportOpts -> Maybe AccountName -> Int -> Amount -> [OutputFormat] -> String
|
||||||
formatBalanceReportItem _ _ _ _ [] = ""
|
formatBalanceReportItem _ _ _ _ [] = ""
|
||||||
formatBalanceReportItem opts accountName depth amount (fmt:fmts) =
|
formatBalanceReportItem opts accountName depth amount (fmt:fmts) =
|
||||||
s ++ (formatBalanceReportItem opts accountName depth amount fmts)
|
s ++ (formatBalanceReportItem opts accountName depth amount fmts)
|
||||||
|
|||||||
@ -104,7 +104,7 @@ import Text.ParserCombinators.Parsec as P
|
|||||||
import Text.Printf
|
import Text.Printf
|
||||||
|
|
||||||
import Hledger
|
import Hledger
|
||||||
import Hledger.Data.FormatStrings as Format
|
import Hledger.Data.OutputFormat as OutputFormat
|
||||||
import Hledger.Cli.Version
|
import Hledger.Cli.Version
|
||||||
|
|
||||||
--
|
--
|
||||||
@ -638,12 +638,12 @@ balancetypeopt rawopts
|
|||||||
|
|
||||||
-- | Parse the format option if provided, possibly returning an error,
|
-- | Parse the format option if provided, possibly returning an error,
|
||||||
-- otherwise get the default value.
|
-- otherwise get the default value.
|
||||||
formatFromOpts :: ReportOpts -> Either String [FormatString]
|
formatFromOpts :: ReportOpts -> Either String [OutputFormat]
|
||||||
formatFromOpts = maybe (Right defaultBalanceFormatString) parseFormatString . format_
|
formatFromOpts = maybe (Right defaultBalanceFormat) parseStringFormat . format_
|
||||||
|
|
||||||
-- | Default line format for balance report: "%20(total) %2(depth_spacer)%-(account)"
|
-- | Default line format for balance report: "%20(total) %2(depth_spacer)%-(account)"
|
||||||
defaultBalanceFormatString :: [FormatString]
|
defaultBalanceFormat :: [OutputFormat]
|
||||||
defaultBalanceFormatString = [
|
defaultBalanceFormat = [
|
||||||
FormatField False (Just 20) Nothing TotalField
|
FormatField False (Just 20) Nothing TotalField
|
||||||
, FormatLiteral " "
|
, FormatLiteral " "
|
||||||
, FormatField True (Just 2) Nothing DepthSpacerField
|
, FormatField True (Just 2) Nothing DepthSpacerField
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user