{-# LANGUAGE TupleSections #-}
module Hcompta.Format.Ledger.Read where
-import Control.Applicative ((<*), (<$>))
+import Control.Applicative ((<$>), (<*>), (<*))
import qualified Control.Exception as Exception
-import Control.Monad (guard, (>=>), liftM)
+import Control.Arrow ((***))
+import Control.Monad (guard, join, liftM, (>=>))
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.Except (ExceptT(..), throwE)
import qualified Data.Char
import qualified Hcompta.Model.Amount.Unit as Unit
import Hcompta.Model.Amount.Unit (Unit)
import qualified Hcompta.Model.Transaction as Transaction
-import Hcompta.Model.Transaction (Transaction)
+import Hcompta.Model.Transaction (Transaction, Comment)
import qualified Hcompta.Model.Transaction.Posting as Posting
import Hcompta.Model.Transaction (Posting)
import qualified Hcompta.Model.Transaction.Tag as Tag
-- ** Combinators
-- | Like 'Text.Parsec.choice' but with 'Text.Parsec.try' on each case.
-choice_try :: Stream s m t => [ParsecT s st m a] -> ParsecT s st m a
+choice_try :: Stream s m t => [ParsecT s u m a] -> ParsecT s u m a
choice_try = Data.List.foldr (\a -> (<|>) (P.try a)) P.parserZero
-- choice_try = P.choice . Data.List.map P.try
-- | Like 'Text.Parsec.sepBy' but without parsing an ending separator.
many_separated
:: Stream s m t
- => ParsecT s st m a
- -> ParsecT s st m b
- -> ParsecT s st m [a]
+ => ParsecT s u m a
+ -> ParsecT s u m b
+ -> ParsecT s u m [a]
many_separated p sep =
many1_separated p sep <|> return []
-- | Like 'Text.Parsec.sepBy1' but without parsing an ending separator.
many1_separated
:: Stream s m t
- => ParsecT s st m a
- -> ParsecT s st m b
- -> ParsecT s st m [a]
+ => ParsecT s u m a
+ -> ParsecT s u m b
+ -> ParsecT s u m [a]
many1_separated p sep = do
x <- p
xs <- P.many (P.try (sep >> p))
return $ x:xs
-- (:) <$> p <*> P.many (P.try (sep >> p))
-and_context
+-- | Make a 'Text.Parsec.ParsecT' also return its user state.
+and_state
:: Stream s m t
- => ParsecT s st m a
- -> ParsecT s st m (a, st)
-and_context p = do
+ => ParsecT s u m a
+ -> ParsecT s u m (a, u)
+and_state p = do
a <- p
s <- P.getState
return (a, s)
Data.List.foldl (\x d ->
base*x + toInteger (Data.Char.digitToInt d)) 0
-decimal :: Stream s m Char => ParsecT s st m Integer
+decimal :: Stream s m Char => ParsecT s u m Integer
decimal = integer 10 P.digit
-hexadecimal :: Stream s m Char => ParsecT s st m Integer
+hexadecimal :: Stream s m Char => ParsecT s u m Integer
hexadecimal = P.oneOf "xX" >> integer 16 P.hexDigit
-octal :: Stream s m Char => ParsecT s st m Integer
+octal :: Stream s m Char => ParsecT s u m Integer
octal = P.oneOf "oO" >> integer 8 P.octDigit
-- | Parse an 'Integer'.
integer :: Stream s m t
- => Integer -> ParsecT s st m Char
- -> ParsecT s st m Integer
+ => Integer
+ -> ParsecT s u m Char
+ -> ParsecT s u m Integer
integer base digit = do
digits <- P.many1 digit
let n = integer_of_digits base digits
seq n (return n)
-- | Parse either '-' into 'negate', or '+' or '' into 'id'.
-sign :: (Stream s m Char, Num i) => ParsecT s st m (i -> i)
+sign :: (Stream s m Char, Num i) => ParsecT s u m (i -> i)
sign =
- (P.char '-' >> return negate) <|>
- (P.char '+' >> return id) <|>
- return id
+ (P.char '-' >> return negate)
+ <|> (P.char '+' >> return id)
+ <|> return id
-- ** Whites
is_space_horizontal :: Char -> Bool
is_space_horizontal c = c /= '\n' && c /= '\r' && Data.Char.isSpace c
-space_horizontal :: Stream s m Char => ParsecT s st m Char
+space_horizontal :: Stream s m Char => ParsecT s u m Char
{-# INLINEABLE space_horizontal #-}
-space_horizontal = P.satisfy is_space_horizontal <?> "horizontal space"
+space_horizontal = P.satisfy is_space_horizontal <?> "horizontal-space"
-newline :: Stream s m Char => ParsecT s st m ()
+newline :: Stream s m Char => ParsecT s u m ()
newline = ((P.try (P.string "\r\n") <|> P.string "\n") >> return ()) <?> "newline"
--- * Parsing 'Account'.
+-- * Parsing 'Account'
account_name_sep :: Char
account_name_sep = ':'
-- | Parse an 'Account'.
-account :: Stream s m Char => ParsecT s st m Account
+account :: Stream s m Char => ParsecT s u m Account
account = do
P.notFollowedBy $ space_horizontal
many1_separated account_name $ P.char account_name_sep
-- | Parse an Account.'Account.Name'.
-account_name :: Stream s m Char => ParsecT s st m Account.Name
+account_name :: Stream s m Char => ParsecT s u m Account.Name
account_name = do
Text.pack <$> do
P.many1 $ P.try account_name_char
where
- account_name_char :: Stream s m Char => ParsecT s st m Char
+ account_name_char :: Stream s m Char => ParsecT s u m Char
account_name_char = do
c <- P.anyChar
case c of
_ -> P.parserZero
-- | Parse an Account.'Account.Joker_Name'.
-account_joker_name :: Stream s m Char => ParsecT s st m Account.Joker_Name
+account_joker_name :: Stream s m Char => ParsecT s u m Account.Joker_Name
account_joker_name = do
n <- P.option Nothing $ (Just <$> account_name)
case n of
Just n' -> return $ Account.Joker_Name n'
-- | Parse an Account.'Account.Joker'.
-account_joker :: Stream s m Char => ParsecT s st m Account.Joker
+account_joker :: Stream s m Char => ParsecT s u m Account.Joker
account_joker = do
P.notFollowedBy $ space_horizontal
many1_separated account_joker_name $ P.char account_name_sep
-- | Parse a 'Regex'.
-account_regex :: Stream s m Char => ParsecT s st m Regex
+account_regex :: Stream s m Char => ParsecT s u m Regex
account_regex = do
re <- P.many1 $ P.satisfy (not . is_space_horizontal)
Regex.of_StringM re
-- | Parse an Account.'Account.Filter'.
-account_pattern :: Stream s m Char => ParsecT s st m Account.Pattern
+account_pattern :: Stream s m Char => ParsecT s u m Account.Pattern
account_pattern = do
choice_try
[ Account.Pattern_Exact <$> (P.char '=' >> account)
, Account.Pattern_Regex <$> (P.option '~' (P.char '~') >> account_regex)
]
--- * Parsing 'Amount'.
+-- * Parsing 'Amount'
-- | Parse an 'Amount'.
-amount :: Stream s m Char => ParsecT s st m Amount
+amount :: Stream s m Char => ParsecT s u m Amount
amount = do
left_signing <- sign
left_unit <-
(fromIntegral place)
(signing mantissa)
, Style.nil
- { Style.fractioning = fractioning
- , Style.grouping_integral = grouping_integral
- , Style.grouping_fractional = grouping_fractional
+ { Style.fractioning
+ , Style.grouping_integral
+ , Style.grouping_fractional
, Style.precision = fromIntegral $ length frac_flat
}
)
- (unit_, side, spaced) <-
+ (unit_, unit_side, unit_spaced) <-
case left_unit of
Just (u, s) ->
return (u, Just Style.Side_Left, Just s)
Amount.Amount
{ Amount.quantity = left_signing $ quantity_
, Amount.style = style
- { Style.unit_side = side
- , Style.unit_spaced = spaced
+ { Style.unit_side
+ , Style.unit_spaced
}
, Amount.unit = unit_
}
=> Char -- ^ Integral grouping separator.
-> Char -- ^ Fractioning separator.
-> Char -- ^ Fractional grouping separator.
- -> ParsecT s st m Quantity
+ -> ParsecT s u m Quantity
quantity int_group_sep frac_sep frac_group_sep = do
(integral, grouping_integral) <- do
h <- P.many P.digit
_ -> groups
-- | Parse an 'Unit'.
-unit :: Stream s m Char => ParsecT s st m Unit
+unit :: Stream s m Char => ParsecT s u m Unit
unit =
(quoted <|> unquoted) <?> "unit"
where
- unquoted :: Stream s m Char => ParsecT s st m Unit
+ unquoted :: Stream s m Char => ParsecT s u m Unit
unquoted =
Text.pack <$> do
P.many1 $
Data.Char.TitlecaseLetter -> True
Data.Char.UppercaseLetter -> True
_ -> False
- quoted :: Stream s m Char => ParsecT s st m Unit
+ quoted :: Stream s m Char => ParsecT s u m Unit
quoted =
Text.pack <$> do
P.between (P.char '"') (P.char '"') $
return ()
-- | Parse the year, month and day separator: '/' or '-'.
-date_separator :: Stream s m Char => ParsecT s st m Char
+date_separator :: Stream s m Char => ParsecT s u m Char
date_separator = P.satisfy (\c -> c == '/' || c == '-')
-- | Parse the hour, minute and second separator: ':'.
-hour_separator :: Stream s m Char => ParsecT s st m Char
+hour_separator :: Stream s m Char => ParsecT s u m Char
hour_separator = P.char ':'
--- * Parsing 'Date'.
+-- * Parsing 'Date'
-- | Parse a 'Date' in [YYYY/]MM/DD [HH:MM[:SS][TZ]] format.
-date :: Stream s m Char => Maybe Integer -> ParsecT s st m Date
+date :: Stream s m Char => Maybe Integer -> ParsecT s u m Date
date def_year = do
n0 <- P.many1 P.digit
- date_sep <- date_separator
+ day_sep <- date_separator
n1 <- P.try (P.count 2 P.digit) <|> P.count 1 P.digit
n2 <- P.option Nothing $ P.try $ do
- _ <- P.char date_sep
+ _ <- P.char day_sep
Just <$> do P.try (P.count 2 P.digit) <|> P.count 1 P.digit
(year, m, d) <-
case (n2, def_year) of
time_zone =
-- DOC: http://www.timeanddate.com/time/zones/
-- TODO: only a few time zones are suported below.
+ -- TODO: check the timeZoneSummerOnly values
P.choice
[ P.char 'A' >> P.choice
[ P.string "ST" >> return (TimeZone ((-4) * 60) False "AST")
- , P.string "DT" >> return (TimeZone ((-3) * 60) False "ADT")
+ , P.string "DT" >> return (TimeZone ((-3) * 60) True "ADT")
, return (TimeZone ((-1) * 60) False "A")
]
, P.char 'B' >> P.choice
]
, P.char 'C' >> P.choice
[ P.char 'E' >> P.choice
- [ P.string "T" >> return (TimeZone ((1) * 60) False "CET")
- , P.string "ST" >> return (TimeZone ((2) * 60) True "CEST")
+ [ P.string "T" >> return (TimeZone ((1) * 60) True "CET")
+ , P.string "ST" >> return (TimeZone ((2) * 60) False "CEST")
]
, P.string "ST" >> return (TimeZone ((-6) * 60) False "CST")
, P.string "DT" >> return (TimeZone ((-5) * 60) True "CDT")
, time_zone_digits
]
-time_zone_digits :: Stream s m Char => ParsecT s st m TimeZone
+time_zone_digits :: Stream s m Char => ParsecT s u m TimeZone
{-# INLINEABLE time_zone_digits #-}
time_zone_digits = do
sign_ <- sign
}
return tz
--- * Parsing 'Comment'.
-
-type Comment = Transaction.Comment
+-- * Parsing 'Comment'
comment_begin :: Char
comment_begin = ';'
-comment :: Stream s m Char => ParsecT s st m Comment
+comment :: Stream s m Char => ParsecT s u m Comment
comment = do
_ <- P.char comment_begin
Text.pack <$> do
P.manyTill P.anyChar (P.lookAhead newline <|> P.eof)
<?> "comment"
-comments :: Stream s m Char => ParsecT s st m [Comment]
+comments :: Stream s m Char => ParsecT s u m [Comment]
comments = do
many_separated comment $
Text.pack <$> do
P.many1 $ P.satisfy Data.Char.isSpace
--- * Parsing 'Tag'.
+-- * Parsing 'Tag'
tag_value_sep :: Char
tag_value_sep = ':'
tag_sep = ','
-- | Parse a 'Tag'.
-tag :: Stream s m Char => ParsecT s st m Tag
+tag :: Stream s m Char => ParsecT s u m Tag
tag = do
n <- tag_name
_ <- P.char tag_value_sep
return (n, v)
<?> "tag"
-tag_name :: Stream s m Char => ParsecT s st m Tag.Name
+tag_name :: Stream s m Char => ParsecT s u m Tag.Name
tag_name = do
+ Text.pack <$> do
P.many1 $ P.satisfy (\c -> c /= tag_value_sep && not (Data.Char.isSpace c))
-tag_value :: Stream s m Char => ParsecT s st m Tag.Value
+tag_value :: Stream s m Char => ParsecT s u m Tag.Value
tag_value = do
+ Text.pack <$> do
P.many $
P.satisfy (\c -> c /= tag_sep && c /= '\n')
-tags :: Stream s m Char => ParsecT s st m Tag.By_Name
+tags :: Stream s m Char => ParsecT s u m Tag.By_Name
tags = do
Tag.from_List <$> do
many_separated tag $ do
P.skipMany $ space_horizontal
return ()
--- * Parsing 'Posting'.
+-- * Parsing 'Posting'
-- | Parse a 'Posting'.
-posting :: Stream s m Char => ParsecT s Context m Posting
+posting :: Stream s m Char => ParsecT s Context m (Posting, Posting.Type)
posting = do
ctx <- P.getState
sourcepos <- P.getPosition
Amount.from_List <$> do
many_separated amount $ P.try $ do
P.skipMany $ space_horizontal
- _ <- P.char '+'
+ _ <- P.char amount_sep
P.skipMany $ space_horizontal
return ()
, return Data.Map.empty
([], Just (_:_)) ->
return $ context_date ctx:dates_
_ -> return $ dates_
- return Posting.Posting
+ return (Posting.Posting
{ Posting.account=account_
, Posting.amounts=amounts_
, Posting.comments=comments_
, Posting.sourcepos=sourcepos
, Posting.status=status_
, Posting.tags=tags_
- , Posting.type_=type_
- }
+ }, type_)
<?> "posting"
+amount_sep :: Char
+amount_sep = '+'
+
tags_of_comments :: [Comment] -> Tag.By_Name
tags_of_comments =
Data.Map.unionsWith (++)
tags <* P.eof)
() "" )
-status :: Stream s m Char => ParsecT s st m Bool
+status :: Stream s m Char => ParsecT s u m Transaction.Status
status =
( P.try $ do
P.skipMany $ space_horizontal
<?> "status"
-- | Parse an 'Account' with Posting.'Posting.Type'.
-account_with_posting_type :: Stream s m Char => ParsecT s st m (Account, Posting.Type)
+account_with_posting_type :: Stream s m Char => ParsecT s u m (Account, Posting.Type)
account_with_posting_type = do
choice_try
- [ (, Posting.Type_Virtual) <$> P.between (P.char '(') (P.char posting_type_virtual_end) account
- , (, Posting.Type_Virtual_Balanced) <$> P.between (P.char '[') (P.char posting_type_virtual_balanced_end) account
+ [ (, Posting.Type_Virtual) <$> P.between (P.char posting_type_virtual_begin)
+ (P.char posting_type_virtual_end)
+ account
+ , (, Posting.Type_Virtual_Balanced) <$> P.between (P.char posting_type_virtual_balanced_begin)
+ (P.char posting_type_virtual_balanced_end)
+ account
, (, Posting.Type_Regular) <$> account
]
+posting_type_virtual_begin :: Char
+posting_type_virtual_begin = '('
+posting_type_virtual_balanced_begin :: Char
+posting_type_virtual_balanced_begin = '['
posting_type_virtual_end :: Char
posting_type_virtual_end = ')'
posting_type_virtual_balanced_end :: Char
posting_type_virtual_balanced_end = ']'
--- * Parsing 'Transaction'.
+-- * Parsing 'Transaction'
transaction :: Stream s m Char => ParsecT s Context m Transaction
transaction = do
date_ <- date (Just $ context_year ctx)
dates_ <-
P.option [] $ P.try $ do
- _ <- P.many $ space_horizontal
- _ <- P.char '='
- _ <- P.many $ space_horizontal
+ P.skipMany $ space_horizontal
+ _ <- P.char date_sep
+ P.skipMany $ space_horizontal
many_separated
(date (Just $ context_year ctx)) $
P.try $ do
P.many $ space_horizontal
- >> P.char '='
+ >> P.char date_sep
>> (P.many $ space_horizontal)
- _ <- P.many $ space_horizontal
+ P.skipMany $ space_horizontal
status_ <- status
code_ <- P.option "" $ P.try code
P.skipMany $ space_horizontal
(tags_of_comments comments_before)
(tags_of_comments comments_after)
newline
- postings_ <- Posting.from_List <$> many1_separated posting (newline)
+ postings_ <- many1_separated posting newline
+ let (postings, postings__) =
+ (Posting.from_List . Data.List.map fst) *** id $
+ Data.List.partition
+ ((Posting.Type_Regular ==) . snd)
+ postings_
+ let (virtual_postings, balanced_virtual_postings) =
+ join (***) (Posting.from_List . Data.List.map fst) $
+ Data.List.partition
+ ((Posting.Type_Virtual ==) . snd)
+ postings__
return $
Transaction.Transaction
{ Transaction.code=code_
- , Transaction.comments_before=comments_before
- , Transaction.comments_after=comments_after
+ , Transaction.comments_before
+ , Transaction.comments_after
, Transaction.dates=(date_, dates_)
, Transaction.description=description_
- , Transaction.postings=postings_
+ , Transaction.postings
+ , Transaction.virtual_postings
+ , Transaction.balanced_virtual_postings
, Transaction.sourcepos
, Transaction.status=status_
, Transaction.tags=tags_
}
<?> "transaction"
+date_sep :: Char
+date_sep = '='
+
code :: Stream s m Char => ParsecT s Context m Transaction.Code
code = do
Text.pack <$> do
P.many $ P.satisfy (\c -> c /= ')' && not (is_space_horizontal c))
<?> "code"
-description :: Stream s m Char => ParsecT s st m Transaction.Description
+description :: Stream s m Char => ParsecT s u m Transaction.Description
description = do
Text.pack <$> do
P.many $ P.try description_char
<?> "description"
where
- description_char :: Stream s m Char => ParsecT s st m Char
+ description_char :: Stream s m Char => ParsecT s u m Char
description_char = do
c <- P.anyChar
case c of
_ | not (Data.Char.isSpace c) -> return c
_ -> P.parserZero
--- * Parsing directives.
+-- * Parsing directives
default_year :: Stream s m Char => ParsecT s Context m ()
default_year = do
include = do
sourcepos <- P.getPosition
P.skipMany1 $ space_horizontal
- (filename::String) <- P.manyTill P.anyChar (P.lookAhead newline <|> P.eof)
+ filename <- P.manyTill P.anyChar (P.lookAhead newline <|> P.eof)
context_ <- P.getState
let journal_ = context_journal context_
let cwd = Path.takeDirectory (P.sourceName sourcepos)
, file_
, ":\n", show (ko::Exception.IOException)
])
- >>= P.runParserT (and_context $ journal_rec file_)
- context_{context_journal=Journal.nil}
+ >>= P.runParserT (and_state $ journal_rec file_)
+ context_{context_journal = Journal.nil}
file_
- >>= \case
+ >>= \case
Left ko -> fail $ show ko
Right ok -> return ok
P.setState $
: Journal.includes journal_}}
<?> "include"
--- * Parsing 'Journal'.
+-- * Parsing 'Journal'
journal :: Stream s IO Char => FilePath -> ParsecT s Context IO Journal
journal file_ = do
- currentUTC <- liftIO $ Time.getCurrentTime
- currentTimeZone <- liftIO $ Time.getCurrentTimeZone
- let currentLocalTime = Time.utcToLocalTime currentTimeZone currentUTC
+ currentLocalTime <- liftIO $
+ Time.utcToLocalTime
+ <$> Time.getCurrentTimeZone
+ <*> Time.getCurrentTime
let (currentLocalYear, _, _) = Time.toGregorian $ Time.localDay currentLocalTime
context_ <- P.getState
P.setState $ context_{context_year=currentLocalYear}
journal_ <- context_journal <$> P.getState
return $
journal_
- { Journal.file=file_
+ { Journal.file = file_
, Journal.last_read_time
, Journal.includes = reverse $ Journal.includes journal_
}
--- ** Parsing 'Journal' from a file.
+-- ** Parsing 'Journal' from a file
file :: FilePath -> ExceptT String IO Journal
file path = do
- content <- ExceptT $
+ ExceptT $
Exception.catch
(liftM Right $ Text.IO.readFile path) $
\ko -> return $ Left $ show (ko::Exception.IOException)
- liftIO $ P.runParserT (journal path) nil_Context path content
+ >>= liftIO . P.runParserT (journal path) nil_Context path
>>= \case
Left ko -> throwE $ show ko
Right ok -> ExceptT $ return $ Right ok
--- /dev/null
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE NamedFieldPuns #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+module Hcompta.Format.Ledger.Write where
+
+import Control.Arrow ((***))
+import Data.Decimal (DecimalRaw(..))
+import qualified Data.Char (isSpace)
+import Data.Fixed (showFixed)
+import qualified Data.List
+import qualified Data.Map.Strict as Data.Map
+import Data.Maybe (fromMaybe)
+import qualified Data.Text.Lazy as TL
+import qualified Data.Text as Text
+import Data.Text (Text)
+import qualified Data.Time.Calendar as Time (toGregorian)
+import qualified Data.Time.LocalTime as Time (LocalTime(..), TimeOfDay(..), TimeZone(..), timeZoneOffsetString, ZonedTime(..))
+import qualified Text.PrettyPrint.Leijen.Text as P
+import Text.PrettyPrint.Leijen.Text (Doc, (<>))
+import System.IO (Handle)
+
+import qualified Hcompta.Model.Account as Account
+import Hcompta.Model.Account (Account)
+import qualified Hcompta.Model.Amount as Amount
+import Hcompta.Model.Amount (Amount)
+import qualified Hcompta.Model.Amount.Quantity as Quantity
+import Hcompta.Model.Amount.Quantity (Quantity)
+import qualified Hcompta.Model.Amount.Style as Style
+import Hcompta.Model.Amount.Style (Style)
+-- import qualified Hcompta.Model.Amount.Unit as Unit
+import Hcompta.Model.Amount.Unit (Unit)
+import qualified Hcompta.Model.Transaction as Transaction
+import Hcompta.Model.Transaction (Comment, Tag, Transaction)
+import qualified Hcompta.Model.Transaction.Posting as Posting
+import Hcompta.Model.Transaction (Posting)
+import qualified Hcompta.Model.Journal as Journal
+import Hcompta.Model.Journal (Journal)
+-- import qualified Hcompta.Model.Transaction.Tag as Tag
+-- import Hcompta.Model.Transaction (Tag)
+-- import qualified Hcompta.Model.Date as Date
+import Hcompta.Model.Date (Date)
+-- import Hcompta.Format.Ledger.Journal as Journal
+import qualified Hcompta.Format.Ledger.Read as Read
+
+-- * Utilities
+
+-- ** Rendering
+
+show :: Doc -> TL.Text
+show = P.displayT . P.renderPretty 1.0 maxBound
+
+showIO :: Handle -> Doc -> IO ()
+showIO handle = P.displayIO handle . P.renderPretty 1.0 maxBound
+
+-- ** Combinators
+
+-- | Return a 'Doc' from a strict 'Text'
+text :: Text -> Doc
+text = P.text . TL.fromStrict
+
+-- | Return a 'Doc' concatenating converted values of a 'Map'
+-- separated by a given 'Doc'
+map_concat
+ :: Doc -> (a -> Doc)
+ -> Data.Map.Map k a -> Doc
+map_concat sep f =
+ snd . Data.Map.foldl
+ (\(first, doc) x -> case first of
+ True -> (False, f x)
+ False -> (False, doc <> sep <> f x))
+ (True, P.empty) -- NOTE: public API gives no way to test for P.empty
+
+-- * Printing 'Account'
+
+account :: Posting.Type -> Account -> Doc
+account type_ =
+ case type_ of
+ Posting.Type_Regular -> account_
+ Posting.Type_Virtual -> \acct ->
+ P.char Read.posting_type_virtual_begin <> do
+ account_ acct <> do
+ P.char Read.posting_type_virtual_end
+ Posting.Type_Virtual_Balanced -> \acct ->
+ P.char Read.posting_type_virtual_balanced_begin <> do
+ account_ acct <> do
+ P.char Read.posting_type_virtual_balanced_end
+ where
+ account_ :: Account -> Doc
+ account_ acct =
+ P.align $ P.hcat $
+ Data.List.intersperse
+ (P.char Read.account_name_sep)
+ (Data.List.map account_name acct)
+
+account_name :: Account.Name -> Doc
+account_name = text
+
+-- ** Mesuring 'Account'
+
+account_length :: Posting.Type -> Account -> Int
+account_length type_ acct =
+ Data.List.foldl
+ (\acc -> (1 +) . (acc +) . Text.length)
+ (if acct == [] then 0 else (- 1)) acct +
+ case type_ of
+ Posting.Type_Regular -> 0
+ Posting.Type_Virtual -> 2
+ Posting.Type_Virtual_Balanced -> 2
+
+-- * Printing 'Amount'
+
+amount :: Amount -> Doc
+amount Amount.Amount
+ { Amount.quantity=qty
+ , Amount.style = style@(Style.Style
+ { Style.unit_side
+ , Style.unit_spaced
+ })
+ , Amount.unit=unit_
+ } = do
+ case unit_side of
+ Just Style.Side_Left ->
+ (unit unit_)
+ <> (case unit_spaced of { Just True | unit_ /= "" -> P.space; _ -> P.empty })
+ _ -> P.empty
+ <> quantity style qty
+ <> case unit_side of
+ (Just Style.Side_Right) ->
+ (case unit_spaced of { Just True | unit_ /= "" -> P.space; _ -> P.empty })
+ <> unit unit_
+ Nothing ->
+ (case unit_spaced of { Just True | unit_ /= "" -> P.space; _ -> P.empty })
+ <> unit unit_
+ _ -> P.empty
+
+unit :: Unit -> Doc
+unit = text
+
+quantity :: Style -> Quantity -> Doc
+quantity Style.Style
+ { Style.fractioning
+ , Style.grouping_integral
+ , Style.grouping_fractional
+ , Style.precision
+ } qty = do
+ let Decimal e n = Quantity.round precision qty
+ let num = Prelude.show $ abs $ n
+ let sign = text (if n < 0 then "-" else "")
+ case e == 0 || precision == 0 of
+ True -> sign <> (text $ Text.pack num)
+ False -> do
+ let num_len = length num
+ let padded =
+ Data.List.concat
+ [ replicate (fromIntegral e + 1 - num_len) '0'
+ , num
+ , replicate (fromIntegral precision - fromIntegral e) '0'
+ ]
+ let (int, frac) = Data.List.splitAt (max 1 (num_len - fromIntegral precision)) padded
+ let default_fractioning =
+ Data.List.head $
+ del_grouping_sep grouping_integral $
+ del_grouping_sep grouping_fractional $
+ ['.', ',']
+ sign <> do
+ P.text (TL.pack $ maybe id (\g -> reverse . group g . reverse) grouping_integral $ int) <> do
+ P.char (fromMaybe default_fractioning fractioning) <> do
+ P.text (TL.pack $ maybe id group grouping_fractional frac)
+ where
+ group :: Style.Grouping -> [Char] -> [Char]
+ group (Style.Grouping sep sizes_) =
+ Data.List.concat . reverse .
+ Data.List.map reverse . fst .
+ Data.List.foldl
+ (flip (\digit -> \case
+ ([], sizes) -> ([[digit]], sizes)
+ (digits:groups, []) -> ((digit:digits):groups, [])
+ (digits:groups, curr_sizes@(size:sizes)) ->
+ if length digits < size
+ then ( (digit:digits):groups, curr_sizes)
+ else ([digit]:[sep]:digits:groups, if sizes == [] then curr_sizes else sizes)
+ ))
+ ([], sizes_)
+ del_grouping_sep grouping =
+ case grouping of
+ Just (Style.Grouping sep _) -> Data.List.delete sep
+ _ -> id
+
+-- ** Mesuring 'Amount'
+
+amount_length :: Amount -> Int
+amount_length Amount.Amount
+ { Amount.quantity=qty
+ , Amount.style = style@(Style.Style
+ { Style.unit_spaced
+ })
+ , Amount.unit=unit_
+ } = do
+ Text.length unit_
+ + (case unit_spaced of { Just True | unit_ /= "" -> 1; _ -> 0 })
+ + quantity_length style qty
+
+amounts_length :: Amount.By_Unit -> Int
+amounts_length amts =
+ if Data.Map.null amts
+ then 0
+ else
+ Data.Map.foldr
+ (\n -> (3 +) . (+) (amount_length n))
+ 0 amts
+
+quantity_length :: Style -> Quantity -> Int
+quantity_length Style.Style
+ { Style.grouping_integral
+ , Style.grouping_fractional
+ , Style.precision
+ } qty =
+ let Decimal e n = Quantity.round precision qty in
+ let sign_len = if n < 0 then 1 else 0 in
+ let fractioning_len = if e > 0 then 1 else 0 in
+ let num_len = if n == 0 then 0 else (1 +) $ truncate $ logBase 10 $ (fromIntegral (abs n)::Double) in
+ let pad_left_len = max 0 (fromIntegral e + 1 - num_len) in
+ let pad_right_len = max 0 (fromIntegral precision - fromIntegral e) in
+ let padded_len = pad_left_len + num_len + pad_right_len in
+ let int_len = max 1 (num_len - fromIntegral precision) in
+ let frac_len = max 0 (padded_len - int_len) in
+ ( sign_len
+ + fractioning_len
+ + padded_len
+ + maybe 0 (group int_len) grouping_integral
+ + maybe 0 (group frac_len) grouping_fractional
+ )
+ where
+ group :: Int -> Style.Grouping -> Int
+ group num_len (Style.Grouping _sep sizes_) =
+ if num_len <= 0
+ then 0
+ else loop 0 num_len sizes_
+ where
+ loop :: Int -> Int -> [Int] -> Int
+ loop pad len =
+ \case
+ [] -> 0
+ sizes@[size] ->
+ let l = len - size in
+ if l <= 0 then pad
+ else loop (pad + 1) l sizes
+ size:sizes ->
+ let l = len - size in
+ if l <= 0 then pad
+ else loop (pad + 1) l sizes
+
+-- * Printing 'Date'
+
+date :: Date -> Doc
+date (Time.ZonedTime
+ (Time.LocalTime day tod)
+ tz@(Time.TimeZone tz_min _ tz_name)) = do
+ let (y, mo, d) = Time.toGregorian day
+ (if y == 0 then P.empty else P.integer y <> P.char '/') <> do
+ int2 mo <> do
+ P.char '/' <> int2 d <> do
+ (case tod of
+ Time.TimeOfDay 0 0 0 -> P.empty
+ Time.TimeOfDay h m s ->
+ P.space <> int2 h <> do
+ P.char ':' <> int2 m <> do
+ (case s of
+ 0 -> P.empty
+ _ -> P.char ':' <> do
+ (if s < 10 then P.char '0' else P.empty) <> do
+ text $ Text.pack $ showFixed True s)) <> do
+ (case tz_min of
+ 0 -> P.empty
+ _ | tz_name /= "" -> P.space <> do text $ Text.pack tz_name
+ _ -> P.space <> do text $ Text.pack $ Time.timeZoneOffsetString tz)
+ where
+ int2 :: Int -> Doc
+ int2 i = if i < 10 then P.char '0' <> P.int i else P.int i
+
+-- * Printing 'Comment'
+
+comment :: Comment -> Doc
+comment com =
+ P.char Read.comment_begin
+ <> (case Text.uncons com of
+ Just (c, _) | not $ Data.Char.isSpace c -> P.space
+ _ -> P.empty)
+ <> text com
+
+comments :: Doc -> [Comment] -> Doc
+comments prefix =
+ P.align . P.hcat .
+ Data.List.intersperse P.line .
+ Data.List.map (\c -> prefix <> comment c)
+
+-- * Printing 'Tag'
+
+tag :: Tag -> Doc
+tag (n, v) = text n <> P.char Read.tag_value_sep <> text v
+
+-- * Printing 'Posting'
+
+posting :: Posting_Lengths -> Posting.Type -> Posting -> Doc
+posting
+ ( max_account_length
+ , max_amount_length
+ )
+ type_
+ Posting.Posting
+ { Posting.account=acct
+ , Posting.amounts
+ , Posting.comments=cmts
+ -- , Posting.dates
+ , Posting.status=status_
+ -- , Posting.tags
+ } =
+ P.char '\t' <> do
+ P.align $ do
+ status status_ <> do
+ (case Data.Map.null amounts of
+ True -> account type_ acct
+ False ->
+ P.fill (max_account_length + 2)
+ (account type_ acct) <> do
+ P.fill (max 0 (max_amount_length - amounts_length amounts)) P.empty <> do
+ -- NOTE: AFAICS Text.PrettyPrint.Leijen gives no way
+ -- to get the column size of a Doc
+ -- before printing it, hence the call to amounts_length here again.
+ map_concat
+ (P.space <> P.char Read.amount_sep <> P.space)
+ amount amounts)
+ <> (case cmts of
+ [] -> P.empty
+ [c] -> P.space <> comment c
+ _ -> P.line <> do comments (P.text "\t\t") cmts)
+
+status :: Transaction.Status -> Doc
+status = \case
+ True -> P.char '!'
+ False -> P.empty
+
+-- ** Mesuring 'Posting'
+
+type Posting_Lengths = (Int, Int)
+
+nil_Posting_Lengths :: Posting_Lengths
+nil_Posting_Lengths = (0, 0)
+
+postings_lengths :: Posting.Type -> Posting.By_Account -> Posting_Lengths -> Posting_Lengths
+postings_lengths type_ =
+ flip $ Data.Map.foldl $ Data.List.foldl $
+ flip $ \p ->
+ (max (account_length type_ (Posting.account p)))
+ ***
+ (max (amounts_length (Posting.amounts p)))
+
+-- * Printing 'Transaction'
+
+transaction :: Transaction -> Doc
+transaction t = transaction_with_lengths (transaction_lengths t nil_Transaction_Lengths) t
+
+transaction_with_lengths :: Transaction_Lengths -> Transaction -> Doc
+transaction_with_lengths
+ posting_lengths_
+ Transaction.Transaction
+ { Transaction.code=code_
+ , Transaction.comments_before
+ , Transaction.comments_after
+ , Transaction.dates=(first_date, dates)
+ , Transaction.description
+ , Transaction.postings
+ , Transaction.virtual_postings
+ , Transaction.balanced_virtual_postings
+ , Transaction.status=status_
+ -- , Transaction.tags
+ } = do
+ (case comments_before of
+ [] -> P.empty
+ _ -> comments (P.text "\t") comments_before <> P.line) <> do
+ (P.hcat $
+ Data.List.intersperse
+ (P.char Read.date_sep)
+ (Data.List.map date (first_date:dates))) <> do
+ (case status_ of
+ True -> P.space <> status status_
+ False -> P.empty) <> do
+ code code_ <> do
+ (case description of
+ "" -> P.empty
+ _ -> P.space <> text description) <> do
+ P.line <> do
+ (case comments_after of
+ [] -> P.empty
+ _ -> comments (P.text "\t") comments_after <> P.line) <> do
+ P.vsep $ Data.List.map
+ (\(type_, ps) ->
+ map_concat P.line
+ (map_concat P.line
+ (P.vsep . Data.List.map
+ (posting posting_lengths_ type_)))
+ (Posting.by_signs_and_account ps))
+ [ (Posting.Type_Regular, postings)
+ , (Posting.Type_Virtual, virtual_postings)
+ , (Posting.Type_Virtual_Balanced, balanced_virtual_postings)
+ ]
+
+code :: Transaction.Code -> Doc
+code = \case
+ "" -> P.empty
+ t -> P.space <> P.char '(' <> text t <> P.char ')'
+
+-- ** Mesuring 'Transaction'
+
+type Transaction_Lengths = Posting_Lengths
+
+nil_Transaction_Lengths :: Posting_Lengths
+nil_Transaction_Lengths = nil_Posting_Lengths
+
+transaction_lengths :: Transaction -> Posting_Lengths -> Posting_Lengths
+transaction_lengths
+ Transaction.Transaction
+ { Transaction.postings
+ , Transaction.virtual_postings
+ , Transaction.balanced_virtual_postings
+ } posting_lengths_ = do
+ Data.List.foldl
+ (flip (\(type_, ps) -> postings_lengths type_ ps))
+ posting_lengths_
+ [ (Posting.Type_Regular, postings)
+ , (Posting.Type_Virtual, virtual_postings)
+ , (Posting.Type_Virtual_Balanced, balanced_virtual_postings)
+ ]
+
+-- * Printing 'Journal'
+
+journal :: Journal -> Doc
+journal Journal.Journal
+ { Journal.transactions
+ } = do
+ let transaction_lengths_ =
+ Data.Map.foldl
+ (Data.List.foldl (flip transaction_lengths))
+ nil_Transaction_Lengths
+ transactions
+ snd $ Data.Map.foldl
+ (Data.List.foldl (\(first, doc) t ->
+ ( False
+ , (if first then P.empty else doc <> P.line)
+ <> transaction_with_lengths transaction_lengths_ t <> P.line
+ )))
+ (True, P.empty)
+ transactions
import qualified Data.Either
import qualified Data.List
import qualified Data.Map.Strict as Data.Map
+import Data.Text (Text)
import qualified Data.Time.Calendar as Time
import qualified Data.Time.LocalTime as Time
import qualified Text.Parsec as P
import qualified Text.Parsec.Pos as P
+-- import qualified Text.PrettyPrint.Leijen.Text as PP
import qualified Hcompta.Model.Account as Account
import qualified Hcompta.Model.Amount as Amount
-import qualified Hcompta.Model.Amount.Style as Style
+import qualified Hcompta.Model.Amount.Style as Amount.Style
+import qualified Hcompta.Model.Date as Date
import qualified Hcompta.Model.Transaction as Transaction
import qualified Hcompta.Model.Transaction.Posting as Posting
import qualified Hcompta.Calc.Balance as Calc.Balance
import qualified Hcompta.Format.Ledger.Read as Format.Ledger.Read
import qualified Hcompta.Format.Ledger.Journal as Format.Ledger.Journal
+import qualified Hcompta.Format.Ledger.Write as Format.Ledger.Write
--instance Eq Text.Parsec.ParseError where
-- (==) = const (const False)
(+)
(Amount.nil
{ Amount.quantity = Decimal 0 1
- , Amount.style = Style.nil
- { Style.unit_side = Just $ Style.Side_Left
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
}
, Amount.unit = "$"
})
(Amount.nil
{ Amount.quantity = Decimal 0 1
- , Amount.style = Style.nil
- { Style.unit_side = Just $ Style.Side_Right
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.unit_side = Just $ Amount.Style.Side_Right
}
, Amount.unit = "$"
})
~?=
(Amount.nil
{ Amount.quantity = Decimal 0 2
- , Amount.style = Style.nil
- { Style.unit_side = Just $ Style.Side_Left
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
}
, Amount.unit = "$"
})
Amount.from_List
[ Amount.nil
{ Amount.quantity = Decimal 0 1
- , Amount.style = Style.nil
- { Style.unit_side = Just $ Style.Side_Left
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
}
, Amount.unit = "$"
}
, Amount.nil
{ Amount.quantity = Decimal 0 1
- , Amount.style = Style.nil
- { Style.unit_side = Just $ Style.Side_Right
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.unit_side = Just $ Amount.Style.Side_Right
}
, Amount.unit = "$"
}
Data.Map.fromList
[ ("$", Amount.nil
{ Amount.quantity = Decimal 0 2
- , Amount.style = Style.nil
- { Style.unit_side = Just $ Style.Side_Left
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.unit_side = Just $ Amount.Style.Side_Left
}
, Amount.unit = "$"
})
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" ""])
+ () "" (""::Text)])
~?=
[]
, "\"A\" = Right \"A\"" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" "A"])
+ () "" ("A"::Text)])
~?=
["A"]
, "\"AA\" = Right \"AA\"" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" "AA"])
+ () "" ("AA"::Text)])
~?=
["AA"]
, "\" \" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" " "])
+ () "" (" "::Text)])
~?=
[]
, "\":\" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" ":"])
+ () "" (":"::Text)])
~?=
[]
, "\"A:\" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" "A:"])
+ () "" ("A:"::Text)])
~?=
[]
, "\":A\" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" ":A"])
+ () "" (":A"::Text)])
~?=
[]
, "\"A \" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" "A "])
+ () "" ("A "::Text)])
~?=
[]
, "\"A \" ^= Right" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name)
- () "" "A "])
+ () "" ("A "::Text)])
~?=
["A"]
, "\"A A\" = Right \"A A\"" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" "A A"])
+ () "" ("A A"::Text)])
~?=
["A A"]
, "\"A \" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" "A "])
+ () "" ("A "::Text)])
~?=
[]
, "\"A \\n\" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" "A \n"])
+ () "" ("A \n"::Text)])
~?=
[]
, "\"(A)A\" = Right \"(A)A\"" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" "(A)A"])
+ () "" ("(A)A"::Text)])
~?=
["(A)A"]
, "\"( )A\" = Right \"( )A\"" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" "( )A"])
+ () "" ("( )A"::Text)])
~?=
["( )A"]
, "\"(A) A\" = Right \"(A) A\"" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" "(A) A"])
+ () "" ("(A) A"::Text)])
~?=
["(A) A"]
, "\"[ ]A\" = Right \"[ ]A\"" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" "[ ]A"])
+ () "" ("[ ]A"::Text)])
~?=
["[ ]A"]
, "\"(A) \" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" "(A) "])
+ () "" ("(A) "::Text)])
~?=
[]
, "\"(A)\" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" "(A)"])
+ () "" ("(A)"::Text)])
~?=
[]
, "\"[A]A\" = Right \"(A)A\"" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" "[A]A"])
+ () "" ("[A]A"::Text)])
~?=
["[A]A"]
, "\"[A] A\" = Right \"[A] A\"" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" "[A] A"])
+ () "" ("[A] A"::Text)])
~?=
["[A] A"]
, "\"[A] \" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" "[A] "])
+ () "" ("[A] "::Text)])
~?=
[]
, "\"[A]\" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account_name <* P.eof)
- () "" "[A]"])
+ () "" ("[A]"::Text)])
~?=
[]
]
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account <* P.eof)
- () "" ""])
+ () "" (""::Text)])
~?=
[]
, "\"A\" = Right [\"A\"]" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account <* P.eof)
- () "" "A"])
+ () "" ("A"::Text)])
~?=
[["A"]]
, "\"A:\" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account <* P.eof)
- () "" "A:"])
+ () "" ("A:"::Text)])
~?=
[]
, "\":A\" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account <* P.eof)
- () "" ":A"])
+ () "" (":A"::Text)])
~?=
[]
, "\"A \" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account <* P.eof)
- () "" "A "])
+ () "" ("A "::Text)])
~?=
[]
, "\" A\" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account <* P.eof)
- () "" " A"])
+ () "" (" A"::Text)])
~?=
[]
, "\"A:B\" = Right [\"A\", \"B\"]" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account <* P.eof)
- () "" "A:B"])
+ () "" ("A:B"::Text)])
~?=
[["A", "B"]]
, "\"A:B:C\" = Right [\"A\", \"B\", \"C\"]" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account <* P.eof)
- () "" "A:B:C"])
+ () "" ("A:B:C"::Text)])
~?=
[["A", "B", "C"]]
, "\"Aa:Bbb:Cccc\" = Right [\"Aa\", \"Bbb\", \":Cccc\"]" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account <* P.eof)
- () "" "Aa:Bbb:Cccc"])
+ () "" ("Aa:Bbb:Cccc"::Text)])
~?=
[["Aa", "Bbb", "Cccc"]]
, "\"A a : B b b : C c c c\" = Right [\"A a \", \" B b b \", \": C c c c\"]" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account <* P.eof)
- () "" "A a : B b b : C c c c"])
+ () "" ("A a : B b b : C c c c"::Text)])
~?=
[["A a ", " B b b ", " C c c c"]]
, "\"A: :C\" = Right [\"A\", \" \", \"C\"]" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account <* P.eof)
- () "" "A: :C"])
+ () "" ("A: :C"::Text)])
~?=
[["A", " ", "C"]]
, "\"A::C\" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.account <* P.eof)
- () "" "A::C"])
+ () "" ("A::C"::Text)])
~?=
[]
]
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" ""])
+ () "" (""::Text)])
~?=
[]
, "\"0\" = Right 0" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "0"])
+ () "" ("0"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 0
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "00"])
+ () "" ("00"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 0
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "0."])
+ () "" ("0."::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 0
, Amount.style =
- Style.nil
- { Style.fractioning = Just '.'
+ Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
}
}]
, "\".0\" = Right 0.0" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" ".0"])
+ () "" (".0"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 0
, Amount.style =
- Style.nil
- { Style.fractioning = Just '.'
- , Style.precision = 1
+ Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.precision = 1
}
}]
, "\"0,\" = Right 0," ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "0,"])
+ () "" ("0,"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 0
, Amount.style =
- Style.nil
- { Style.fractioning = Just ','
+ Amount.Style.nil
+ { Amount.Style.fractioning = Just ','
}
}]
, "\",0\" = Right 0,0" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" ",0"])
+ () "" (",0"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 0
, Amount.style =
- Style.nil
- { Style.fractioning = Just ','
- , Style.precision = 1
+ Amount.Style.nil
+ { Amount.Style.fractioning = Just ','
+ , Amount.Style.precision = 1
}
}]
, "\"0_\" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "0_"])
+ () "" ("0_"::Text)])
~?=
[]
, "\"_0\" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "_0"])
+ () "" ("_0"::Text)])
~?=
[]
, "\"0.0\" = Right 0.0" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "0.0"])
+ () "" ("0.0"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 0
, Amount.style =
- Style.nil
- { Style.fractioning = Just '.'
- , Style.precision = 1
+ Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.precision = 1
}
}]
, "\"00.00\" = Right 0.00" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "00.00"])
+ () "" ("00.00"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 0
, Amount.style =
- Style.nil
- { Style.fractioning = Just '.'
- , Style.precision = 2
+ Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.precision = 2
}
}]
, "\"0,0\" = Right 0,0" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "0,0"])
+ () "" ("0,0"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 0
, Amount.style =
- Style.nil
- { Style.fractioning = Just ','
- , Style.precision = 1
+ Amount.Style.nil
+ { Amount.Style.fractioning = Just ','
+ , Amount.Style.precision = 1
}
}]
, "\"00,00\" = Right 0,00" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "00,00"])
+ () "" ("00,00"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 0
, Amount.style =
- Style.nil
- { Style.fractioning = Just ','
- , Style.precision = 2
+ Amount.Style.nil
+ { Amount.Style.fractioning = Just ','
+ , Amount.Style.precision = 2
}
}]
, "\"0_0\" = Right 0" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "0_0"])
+ () "" ("0_0"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 0
, Amount.style =
- Style.nil
- { Style.fractioning = Nothing
- , Style.grouping_integral = Just $ Style.Grouping '_' [1]
- , Style.precision = 0
+ Amount.Style.nil
+ { Amount.Style.fractioning = Nothing
+ , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1]
+ , Amount.Style.precision = 0
}
}]
, "\"00_00\" = Right 0" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "00_00"])
+ () "" ("00_00"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 0
, Amount.style =
- Style.nil
- { Style.fractioning = Nothing
- , Style.grouping_integral = Just $ Style.Grouping '_' [2]
- , Style.precision = 0
+ Amount.Style.nil
+ { Amount.Style.fractioning = Nothing
+ , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2]
+ , Amount.Style.precision = 0
}
}]
, "\"0,000.00\" = Right 0,000.00" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "0,000.00"])
+ () "" ("0,000.00"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 0
, Amount.style =
- Style.nil
- { Style.fractioning = Just '.'
- , Style.grouping_integral = Just $ Style.Grouping ',' [3]
- , Style.precision = 2
+ Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
+ , Amount.Style.precision = 2
}
}]
, "\"0.000,00\" = Right 0.000,00" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount)
- () "" "0.000,00"])
+ () "" ("0.000,00"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 0
, Amount.style =
- Style.nil
- { Style.fractioning = Just ','
- , Style.grouping_integral = Just $ Style.Grouping '.' [3]
- , Style.precision = 2
+ Amount.Style.nil
+ { Amount.Style.fractioning = Just ','
+ , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
+ , Amount.Style.precision = 2
}
}]
, "\"1,000.00\" = Right 1,000.00" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "1,000.00"])
+ () "" ("1,000.00"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 1000
, Amount.style =
- Style.nil
- { Style.fractioning = Just '.'
- , Style.grouping_integral = Just $ Style.Grouping ',' [3]
- , Style.precision = 2
+ Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
+ , Amount.Style.precision = 2
}
}]
, "\"1.000,00\" = Right 1.000,00" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount)
- () "" "1.000,00"])
+ () "" ("1.000,00"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 1000
, Amount.style =
- Style.nil
- { Style.fractioning = Just ','
- , Style.grouping_integral = Just $ Style.Grouping '.' [3]
- , Style.precision = 2
+ Amount.Style.nil
+ { Amount.Style.fractioning = Just ','
+ , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
+ , Amount.Style.precision = 2
}
}]
, "\"1,000.00.\" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount)
- () "" "1,000.00."])
+ () "" ("1,000.00."::Text)])
~?=
[]
, "\"1.000,00,\" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount)
- () "" "1.000,00,"])
+ () "" ("1.000,00,"::Text)])
~?=
[]
, "\"1,000.00_\" = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount)
- () "" "1,000.00_"])
+ () "" ("1,000.00_"::Text)])
~?=
[]
, "\"12\" = Right 12" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "123"])
+ () "" ("123"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 123
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "1.2"])
+ () "" ("1.2"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 1 12
, Amount.style =
- Style.nil
- { Style.fractioning = Just '.'
- , Style.precision = 1
+ Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.precision = 1
}
}]
, "\"1,2\" = Right 1,2" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "1,2"])
+ () "" ("1,2"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 1 12
, Amount.style =
- Style.nil
- { Style.fractioning = Just ','
- , Style.precision = 1
+ Amount.Style.nil
+ { Amount.Style.fractioning = Just ','
+ , Amount.Style.precision = 1
}
}]
, "\"12.23\" = Right 12.23" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "12.34"])
+ () "" ("12.34"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 2 1234
, Amount.style =
- Style.nil
- { Style.fractioning = Just '.'
- , Style.precision = 2
+ Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.precision = 2
}
}]
, "\"12,23\" = Right 12,23" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "12,34"])
+ () "" ("12,34"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 2 1234
, Amount.style =
- Style.nil
- { Style.fractioning = Just ','
- , Style.precision = 2
+ Amount.Style.nil
+ { Amount.Style.fractioning = Just ','
+ , Amount.Style.precision = 2
}
}]
, "\"1_2\" = Right 1_2" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "1_2"])
+ () "" ("1_2"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 12
, Amount.style =
- Style.nil
- { Style.grouping_integral = Just $ Style.Grouping '_' [1]
- , Style.precision = 0
+ Amount.Style.nil
+ { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [1]
+ , Amount.Style.precision = 0
}
}]
, "\"1_23\" = Right 1_23" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "1_23"])
+ () "" ("1_23"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 123
, Amount.style =
- Style.nil
- { Style.grouping_integral = Just $ Style.Grouping '_' [2]
- , Style.precision = 0
+ Amount.Style.nil
+ { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [2]
+ , Amount.Style.precision = 0
}
}]
, "\"1_23_456\" = Right 1_23_456" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "1_23_456"])
+ () "" ("1_23_456"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 123456
, Amount.style =
- Style.nil
- { Style.grouping_integral = Just $ Style.Grouping '_' [3, 2]
- , Style.precision = 0
+ Amount.Style.nil
+ { Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2]
+ , Amount.Style.precision = 0
}
}]
, "\"1_23_456.7890_12345_678901\" = Right 1_23_456.7890_12345_678901" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "1_23_456.7890_12345_678901"])
+ () "" ("1_23_456.7890_12345_678901"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 15 123456789012345678901
, Amount.style =
- Style.nil
- { Style.fractioning = Just '.'
- , Style.grouping_integral = Just $ Style.Grouping '_' [3, 2]
- , Style.grouping_fractional = Just $ Style.Grouping '_' [4, 5, 6]
- , Style.precision = 15
+ Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [3, 2]
+ , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping '_' [4, 5, 6]
+ , Amount.Style.precision = 15
}
}]
, "\"123456_78901_2345.678_90_1\" = Right 123456_78901_2345.678_90_1" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "123456_78901_2345.678_90_1"])
+ () "" ("123456_78901_2345.678_90_1"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 6 123456789012345678901
, Amount.style =
- Style.nil
- { Style.fractioning = Just '.'
- , Style.grouping_integral = Just $ Style.Grouping '_' [4, 5, 6]
- , Style.grouping_fractional = Just $ Style.Grouping '_' [3, 2]
- , Style.precision = 6
+ Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '_' [4, 5, 6]
+ , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping '_' [3, 2]
+ , Amount.Style.precision = 6
}
}]
, "\"$1\" = Right $1" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "$1"])
+ () "" ("$1"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 1
, Amount.style =
- Style.nil
- { Style.fractioning = Nothing
- , Style.grouping_integral = Nothing
- , Style.grouping_fractional = Nothing
- , Style.precision = 0
- , Style.unit_side = Just Style.Side_Left
- , Style.unit_spaced = Just False
+ Amount.Style.nil
+ { Amount.Style.fractioning = Nothing
+ , Amount.Style.grouping_integral = Nothing
+ , Amount.Style.grouping_fractional = Nothing
+ , Amount.Style.precision = 0
+ , Amount.Style.unit_side = Just Amount.Style.Side_Left
+ , Amount.Style.unit_spaced = Just False
}
, Amount.unit = "$"
}]
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "1$"])
+ () "" ("1$"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 1
, Amount.style =
- Style.nil
- { Style.fractioning = Nothing
- , Style.grouping_integral = Nothing
- , Style.grouping_fractional = Nothing
- , Style.precision = 0
- , Style.unit_side = Just Style.Side_Right
- , Style.unit_spaced = Just False
+ Amount.Style.nil
+ { Amount.Style.fractioning = Nothing
+ , Amount.Style.grouping_integral = Nothing
+ , Amount.Style.grouping_fractional = Nothing
+ , Amount.Style.precision = 0
+ , Amount.Style.unit_side = Just Amount.Style.Side_Right
+ , Amount.Style.unit_spaced = Just False
}
, Amount.unit = "$"
}]
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "$ 1"])
+ () "" ("$ 1"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 1
, Amount.style =
- Style.nil
- { Style.fractioning = Nothing
- , Style.grouping_integral = Nothing
- , Style.grouping_fractional = Nothing
- , Style.precision = 0
- , Style.unit_side = Just Style.Side_Left
- , Style.unit_spaced = Just True
+ Amount.Style.nil
+ { Amount.Style.fractioning = Nothing
+ , Amount.Style.grouping_integral = Nothing
+ , Amount.Style.grouping_fractional = Nothing
+ , Amount.Style.precision = 0
+ , Amount.Style.unit_side = Just Amount.Style.Side_Left
+ , Amount.Style.unit_spaced = Just True
}
, Amount.unit = "$"
}]
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "1 $"])
+ () "" ("1 $"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 1
, Amount.style =
- Style.nil
- { Style.fractioning = Nothing
- , Style.grouping_integral = Nothing
- , Style.grouping_fractional = Nothing
- , Style.precision = 0
- , Style.unit_side = Just Style.Side_Right
- , Style.unit_spaced = Just True
+ Amount.Style.nil
+ { Amount.Style.fractioning = Nothing
+ , Amount.Style.grouping_integral = Nothing
+ , Amount.Style.grouping_fractional = Nothing
+ , Amount.Style.precision = 0
+ , Amount.Style.unit_side = Just Amount.Style.Side_Right
+ , Amount.Style.unit_spaced = Just True
}
, Amount.unit = "$"
}]
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "-$1"])
+ () "" ("-$1"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 (-1)
, Amount.style =
- Style.nil
- { Style.fractioning = Nothing
- , Style.grouping_integral = Nothing
- , Style.grouping_fractional = Nothing
- , Style.precision = 0
- , Style.unit_side = Just Style.Side_Left
- , Style.unit_spaced = Just False
+ Amount.Style.nil
+ { Amount.Style.fractioning = Nothing
+ , Amount.Style.grouping_integral = Nothing
+ , Amount.Style.grouping_fractional = Nothing
+ , Amount.Style.precision = 0
+ , Amount.Style.unit_side = Just Amount.Style.Side_Left
+ , Amount.Style.unit_spaced = Just False
}
, Amount.unit = "$"
}]
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "\"4 2\"1"])
+ () "" ("\"4 2\"1"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 1
, Amount.style =
- Style.nil
- { Style.fractioning = Nothing
- , Style.grouping_integral = Nothing
- , Style.grouping_fractional = Nothing
- , Style.precision = 0
- , Style.unit_side = Just Style.Side_Left
- , Style.unit_spaced = Just False
+ Amount.Style.nil
+ { Amount.Style.fractioning = Nothing
+ , Amount.Style.grouping_integral = Nothing
+ , Amount.Style.grouping_fractional = Nothing
+ , Amount.Style.precision = 0
+ , Amount.Style.unit_side = Just Amount.Style.Side_Left
+ , Amount.Style.unit_spaced = Just False
}
, Amount.unit = "4 2"
}]
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "1\"4 2\""])
+ () "" ("1\"4 2\""::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 1
, Amount.style =
- Style.nil
- { Style.fractioning = Nothing
- , Style.grouping_integral = Nothing
- , Style.grouping_fractional = Nothing
- , Style.precision = 0
- , Style.unit_side = Just Style.Side_Right
- , Style.unit_spaced = Just False
+ Amount.Style.nil
+ { Amount.Style.fractioning = Nothing
+ , Amount.Style.grouping_integral = Nothing
+ , Amount.Style.grouping_fractional = Nothing
+ , Amount.Style.precision = 0
+ , Amount.Style.unit_side = Just Amount.Style.Side_Right
+ , Amount.Style.unit_spaced = Just False
}
, Amount.unit = "4 2"
}]
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "$1.000,00"])
+ () "" ("$1.000,00"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 1000
, Amount.style =
- Style.nil
- { Style.fractioning = Just ','
- , Style.grouping_integral = Just $ Style.Grouping '.' [3]
- , Style.grouping_fractional = Nothing
- , Style.precision = 2
- , Style.unit_side = Just Style.Side_Left
- , Style.unit_spaced = Just False
+ Amount.Style.nil
+ { Amount.Style.fractioning = Just ','
+ , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
+ , Amount.Style.grouping_fractional = Nothing
+ , Amount.Style.precision = 2
+ , Amount.Style.unit_side = Just Amount.Style.Side_Left
+ , Amount.Style.unit_spaced = Just False
}
, Amount.unit = "$"
}]
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.amount <* P.eof)
- () "" "1.000,00$"])
+ () "" ("1.000,00$"::Text)])
~?=
[Amount.nil
{ Amount.quantity = Decimal 0 1000
, Amount.style =
- Style.nil
- { Style.fractioning = Just ','
- , Style.grouping_integral = Just $ Style.Grouping '.' [3]
- , Style.grouping_fractional = Nothing
- , Style.precision = 2
- , Style.unit_side = Just Style.Side_Right
- , Style.unit_spaced = Just False
+ Amount.Style.nil
+ { Amount.Style.fractioning = Just ','
+ , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping '.' [3]
+ , Amount.Style.grouping_fractional = Nothing
+ , Amount.Style.precision = 2
+ , Amount.Style.unit_side = Just Amount.Style.Side_Right
+ , Amount.Style.unit_spaced = Just False
}
, Amount.unit = "$"
}]
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.comment <* P.eof)
- () "" "; some comment"])
+ () "" ("; some comment"::Text)])
~?=
[ " some comment" ]
, "; some comment \\n = Right \" some comment \"" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.comment <* P.newline <* P.eof)
- () "" "; some comment \n"])
+ () "" ("; some comment \n"::Text)])
~?=
[ " some comment " ]
, "; some comment \\r\\n = Right \" some comment \"" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.comment <* P.string "\r\n" <* P.eof)
- () "" "; some comment \r\n"])
+ () "" ("; some comment \r\n"::Text)])
~?=
[ " some comment " ]
]
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.comments <* P.eof)
- () "" "; some comment\n ; some other comment"])
+ () "" ("; some comment\n ; some other comment"::Text)])
~?=
[ [" some comment", " some other comment"] ]
, "; some comment \\n = Right \" some comment \"" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.comments <* P.string "\n" <* P.eof)
- () "" "; some comment \n"])
+ () "" ("; some comment \n"::Text)])
~?=
[ [" some comment "] ]
]
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.date Nothing <* P.eof)
- () "" "2000/01/01"])
+ () "" ("2000/01/01"::Text)])
~?=
[ Time.ZonedTime
(Time.LocalTime
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.date Nothing)
- () "" "2000/01/01 some text"])
+ () "" ("2000/01/01 some text"::Text)])
~?=
[ Time.ZonedTime
(Time.LocalTime
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.date Nothing <* P.eof)
- () "" "2000/01/01 12:34"])
+ () "" ("2000/01/01 12:34"::Text)])
~?=
[ Time.ZonedTime
(Time.LocalTime
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.date Nothing <* P.eof)
- () "" "2000/01/01 12:34:56"])
+ () "" ("2000/01/01 12:34:56"::Text)])
~?=
[ Time.ZonedTime
(Time.LocalTime
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.date Nothing <* P.eof)
- () "" "2000/01/01 12:34 CET"])
+ () "" ("2000/01/01 12:34 CET"::Text)])
~?=
[ Time.ZonedTime
(Time.LocalTime
(Time.fromGregorian 2000 01 01)
(Time.TimeOfDay 12 34 0))
- (Time.TimeZone 60 False "CET")]
+ (Time.TimeZone 60 True "CET")]
, "2000/01/01 12:34 +0130 = Right 2000/01/01 12:34 +0130" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.date Nothing <* P.eof)
- () "" "2000/01/01 12:34 +0130"])
+ () "" ("2000/01/01 12:34 +0130"::Text)])
~?=
[ Time.ZonedTime
(Time.LocalTime
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.date Nothing <* P.eof)
- () "" "2000/01/01 12:34:56 CET"])
+ () "" ("2000/01/01 12:34:56 CET"::Text)])
~?=
[ Time.ZonedTime
(Time.LocalTime
(Time.fromGregorian 2000 01 01)
(Time.TimeOfDay 12 34 56))
- (Time.TimeZone 60 False "CET")]
+ (Time.TimeZone 60 True "CET")]
, "2001/02/29 = Left" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.date Nothing <* P.eof)
- () "" "2001/02/29"])
+ () "" ("2001/02/29"::Text)])
~?=
[]
, "01/01 = Right default_year/01/01" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.date (Just 2000) <* P.eof)
- () "" "01/01"])
+ () "" ("01/01"::Text)])
~?=
[ Time.ZonedTime
(Time.LocalTime
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.tag <* P.eof)
- () "" "Name:"])
+ () "" ("Name:"::Text)])
~?=
[("Name", "")]
, "Name:Value = Right Name:Value" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.tag <* P.eof)
- () "" "Name:Value"])
+ () "" ("Name:Value"::Text)])
~?=
[("Name", "Value")]
, "Name:Val ue = Right Name:Val ue" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.tag <* P.eof)
- () "" "Name:Val ue"])
+ () "" ("Name:Val ue"::Text)])
~?=
[("Name", "Val ue")]
]
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.tags <* P.eof)
- () "" "Name:"])
+ () "" ("Name:"::Text)])
~?=
[Data.Map.fromList
[ ("Name", [""])
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.tags <* P.char ',' <* P.eof)
- () "" "Name:,"])
+ () "" ("Name:,"::Text)])
~?=
[Data.Map.fromList
[ ("Name", [""])
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.tags <* P.eof)
- () "" "Name:,Name:"])
+ () "" ("Name:,Name:"::Text)])
~?=
[Data.Map.fromList
[ ("Name", ["", ""])
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.tags <* P.eof)
- () "" "Name:,Name2:"])
+ () "" ("Name:,Name2:"::Text)])
~?=
[Data.Map.fromList
[ ("Name", [""])
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.tags <* P.eof)
- () "" "Name: , Name2:"])
+ () "" ("Name: , Name2:"::Text)])
~?=
[Data.Map.fromList
[ ("Name", [" "])
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.tags <* P.eof)
- () "" "Name:,Name2:,Name3:"])
+ () "" ("Name:,Name2:,Name3:"::Text)])
~?=
[Data.Map.fromList
[ ("Name", [""])
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.tags <* P.eof)
- () "" "Name:Val ue,Name2:V a l u e,Name3:V al ue"])
+ () "" ("Name:Val ue,Name2:V a l u e,Name3:V al ue"::Text)])
~?=
[Data.Map.fromList
[ ("Name", ["Val ue"])
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.posting <* P.eof)
- Format.Ledger.Read.nil_Context "" " A:B:C"])
+ Format.Ledger.Read.nil_Context "" (" A:B:C"::Text)])
~?=
- [ Posting.nil
- { Posting.account = ["A","B","C"]
- , Posting.sourcepos = P.newPos "" 1 1
- }
+ [ ( Posting.nil
+ { Posting.account = ["A","B","C"]
+ , Posting.sourcepos = P.newPos "" 1 1
+ }
+ , Posting.Type_Regular
+ )
]
, " !A:B:C = Right !A:B:C" ~:
- (Data.Either.rights $
+ (Data.List.map fst $
+ Data.Either.rights $
[P.runParser
(Format.Ledger.Read.posting <* P.eof)
- Format.Ledger.Read.nil_Context "" " !A:B:C"])
+ Format.Ledger.Read.nil_Context "" (" !A:B:C"::Text)])
~?=
[ Posting.nil
{ Posting.account = ["A","B","C"]
}
]
, " *A:B:C = Right *A:B:C" ~:
- (Data.Either.rights $
+ (Data.List.map fst $
+ Data.Either.rights $
[P.runParser
(Format.Ledger.Read.posting <* P.eof)
- Format.Ledger.Read.nil_Context "" " *A:B:C"])
+ Format.Ledger.Read.nil_Context "" (" *A:B:C"::Text)])
~?=
[ Posting.nil
{ Posting.account = ["A","B","C"]
, Posting.status = True
, Posting.sourcepos = P.newPos "" 1 1
, Posting.tags = Data.Map.fromList []
- , Posting.type_ = Posting.Type_Regular
}
]
, " A:B:C $1 = Right A:B:C $1" ~:
- (Data.Either.rights $
+ (Data.List.map fst $
+ Data.Either.rights $
[P.runParser
(Format.Ledger.Read.posting <* P.eof)
- Format.Ledger.Read.nil_Context "" " A:B:C $1"])
+ Format.Ledger.Read.nil_Context "" (" A:B:C $1"::Text)])
~?=
[ Posting.nil
{ Posting.account = ["A","B","C $1"]
}
]
, " A:B:C $1 = Right A:B:C $1" ~:
- (Data.Either.rights $
+ (Data.List.map fst $
+ Data.Either.rights $
[P.runParser
(Format.Ledger.Read.posting <* P.eof)
- Format.Ledger.Read.nil_Context "" " A:B:C $1"])
+ Format.Ledger.Read.nil_Context "" (" A:B:C $1"::Text)])
~?=
[ Posting.nil
{ Posting.account = ["A","B","C"]
, Posting.amounts = Data.Map.fromList
[ ("$", Amount.nil
{ Amount.quantity = 1
- , Amount.style = Style.nil
- { Style.unit_side = Just Style.Side_Left
- , Style.unit_spaced = Just False
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.unit_side = Just Amount.Style.Side_Left
+ , Amount.Style.unit_spaced = Just False
}
, Amount.unit = "$"
})
}
]
, " A:B:C $1 + 1€ = Right A:B:C $1 + 1€" ~:
- (Data.Either.rights $
+ (Data.List.map fst $
+ Data.Either.rights $
[P.runParser
(Format.Ledger.Read.posting <* P.eof)
- Format.Ledger.Read.nil_Context "" " A:B:C $1 + 1€"])
+ Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1€"::Text)])
~?=
[ Posting.nil
{ Posting.account = ["A","B","C"]
, Posting.amounts = Data.Map.fromList
[ ("$", Amount.nil
{ Amount.quantity = 1
- , Amount.style = Style.nil
- { Style.unit_side = Just Style.Side_Left
- , Style.unit_spaced = Just False
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.unit_side = Just Amount.Style.Side_Left
+ , Amount.Style.unit_spaced = Just False
}
, Amount.unit = "$"
})
, ("€", Amount.nil
{ Amount.quantity = 1
- , Amount.style = Style.nil
- { Style.unit_side = Just Style.Side_Right
- , Style.unit_spaced = Just False
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.unit_side = Just Amount.Style.Side_Right
+ , Amount.Style.unit_spaced = Just False
}
, Amount.unit = "€"
})
}
]
, " A:B:C $1 + 1$ = Right A:B:C $2" ~:
- (Data.Either.rights $
+ (Data.List.map fst $
+ Data.Either.rights $
[P.runParser
(Format.Ledger.Read.posting <* P.eof)
- Format.Ledger.Read.nil_Context "" " A:B:C $1 + 1$"])
+ Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1$"::Text)])
~?=
[ Posting.nil
{ Posting.account = ["A","B","C"]
, Posting.amounts = Data.Map.fromList
[ ("$", Amount.nil
{ Amount.quantity = 2
- , Amount.style = Style.nil
- { Style.unit_side = Just Style.Side_Left
- , Style.unit_spaced = Just False
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.unit_side = Just Amount.Style.Side_Left
+ , Amount.Style.unit_spaced = Just False
}
, Amount.unit = "$"
})
}
]
, " A:B:C $1 + 1$ + 1$ = Right A:B:C $3" ~:
- (Data.Either.rights $
+ (Data.List.map fst $
+ Data.Either.rights $
[P.runParser
(Format.Ledger.Read.posting <* P.eof)
- Format.Ledger.Read.nil_Context "" " A:B:C $1 + 1$ + 1$"])
+ Format.Ledger.Read.nil_Context "" (" A:B:C $1 + 1$ + 1$"::Text)])
~?=
[ Posting.nil
{ Posting.account = ["A","B","C"]
, Posting.amounts = Data.Map.fromList
[ ("$", Amount.nil
{ Amount.quantity = 3
- , Amount.style = Style.nil
- { Style.unit_side = Just Style.Side_Left
- , Style.unit_spaced = Just False
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.unit_side = Just Amount.Style.Side_Left
+ , Amount.Style.unit_spaced = Just False
}
, Amount.unit = "$"
})
}
]
, " A:B:C ; some comment = Right A:B:C ; some comment" ~:
- (Data.Either.rights $
+ (Data.List.map fst $
+ Data.Either.rights $
[P.runParser
(Format.Ledger.Read.posting <* P.eof)
- Format.Ledger.Read.nil_Context "" " A:B:C ; some comment"])
+ Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment"::Text)])
~?=
[ Posting.nil
{ Posting.account = ["A","B","C"]
}
]
, " A:B:C ; some comment\\n ; some other comment = Right A:B:C ; some comment\\n ; some other comment" ~:
- (Data.Either.rights $
+ (Data.List.map fst $
+ Data.Either.rights $
[P.runParser
(Format.Ledger.Read.posting <* P.eof)
- Format.Ledger.Read.nil_Context "" " A:B:C ; some comment\n ; some other comment"])
+ Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment\n ; some other comment"::Text)])
~?=
[ Posting.nil
{ Posting.account = ["A","B","C"]
}
]
, " A:B:C $1 ; some comment = Right A:B:C $1 ; some comment" ~:
- (Data.Either.rights $
+ (Data.List.map fst $
+ Data.Either.rights $
[P.runParser
(Format.Ledger.Read.posting)
- Format.Ledger.Read.nil_Context "" " A:B:C $1 ; some comment"])
+ Format.Ledger.Read.nil_Context "" (" A:B:C $1 ; some comment"::Text)])
~?=
[ Posting.nil
{ Posting.account = ["A","B","C"]
, Posting.amounts = Data.Map.fromList
[ ("$", Amount.nil
{ Amount.quantity = 1
- , Amount.style = Style.nil
- { Style.unit_side = Just Style.Side_Left
- , Style.unit_spaced = Just False
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.unit_side = Just Amount.Style.Side_Left
+ , Amount.Style.unit_spaced = Just False
}
, Amount.unit = "$"
})
}
]
, " A:B:C ; N:V = Right A:B:C ; N:V" ~:
- (Data.Either.rights $
+ (Data.List.map fst $
+ Data.Either.rights $
[P.runParser
(Format.Ledger.Read.posting <* P.eof)
- Format.Ledger.Read.nil_Context "" " A:B:C ; N:V"])
+ Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V"::Text)])
~?=
[ Posting.nil
{ Posting.account = ["A","B","C"]
}
]
, " A:B:C ; some comment N:V = Right A:B:C ; some comment N:V" ~:
- (Data.Either.rights $
+ (Data.List.map fst $
+ Data.Either.rights $
[P.runParser
(Format.Ledger.Read.posting <* P.eof)
- Format.Ledger.Read.nil_Context "" " A:B:C ; some comment N:V"])
+ Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment N:V"::Text)])
~?=
[ Posting.nil
{ Posting.account = ["A","B","C"]
}
]
, " A:B:C ; some comment N:V v, N2:V2 v2 = Right A:B:C ; some comment N:V v, N2:V2 v2" ~:
- (Data.Either.rights $
+ (Data.List.map fst $
+ Data.Either.rights $
[P.runParser
(Format.Ledger.Read.posting )
- Format.Ledger.Read.nil_Context "" " A:B:C ; some comment N:V v, N2:V2 v2"])
+ Format.Ledger.Read.nil_Context "" (" A:B:C ; some comment N:V v, N2:V2 v2"::Text)])
~?=
[ Posting.nil
{ Posting.account = ["A","B","C"]
}
]
, " A:B:C ; N:V\\n ; N:V2 = Right A:B:C ; N:V\\n ; N:V2" ~:
- (Data.Either.rights $
+ (Data.List.map fst $
+ Data.Either.rights $
[P.runParser
(Format.Ledger.Read.posting <* P.eof)
- Format.Ledger.Read.nil_Context "" " A:B:C ; N:V\n ; N:V2"])
+ Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V\n ; N:V2"::Text)])
~?=
[ Posting.nil
{ Posting.account = ["A","B","C"]
}
]
, " A:B:C ; N:V\\n ; N2:V = Right A:B:C ; N:V\\n ; N2:V" ~:
- (Data.Either.rights $
+ (Data.List.map fst $
+ Data.Either.rights $
[P.runParser
(Format.Ledger.Read.posting <* P.eof)
- Format.Ledger.Read.nil_Context "" " A:B:C ; N:V\n ; N2:V"])
+ Format.Ledger.Read.nil_Context "" (" A:B:C ; N:V\n ; N2:V"::Text)])
~?=
[ Posting.nil
{ Posting.account = ["A","B","C"]
}
]
, " A:B:C ; date:2001/01/01 = Right A:B:C ; date:2001/01/01" ~:
- (Data.Either.rights $
+ (Data.List.map fst $
+ Data.Either.rights $
[P.runParser
(Format.Ledger.Read.posting <* P.eof)
- Format.Ledger.Read.nil_Context "" " A:B:C ; date:2001/01/01"])
+ Format.Ledger.Read.nil_Context "" (" A:B:C ; date:2001/01/01"::Text)])
~?=
[ Posting.nil
{ Posting.account = ["A","B","C"]
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.posting <* P.eof)
- Format.Ledger.Read.nil_Context "" " (A:B:C)"])
+ Format.Ledger.Read.nil_Context "" (" (A:B:C)"::Text)])
~?=
- [ Posting.nil
- { Posting.account = ["A","B","C"]
- , Posting.sourcepos = P.newPos "" 1 1
- , Posting.type_ = Posting.Type_Virtual
- }
+ [ ( Posting.nil
+ { Posting.account = ["A","B","C"]
+ , Posting.sourcepos = P.newPos "" 1 1
+ }
+ , Posting.Type_Virtual
+ )
]
, " [A:B:C] = Right [A:B:C]" ~:
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.posting <* P.eof)
- Format.Ledger.Read.nil_Context "" " [A:B:C]"])
+ Format.Ledger.Read.nil_Context "" (" [A:B:C]"::Text)])
~?=
- [ Posting.nil
- { Posting.account = ["A","B","C"]
- , Posting.sourcepos = P.newPos "" 1 1
- , Posting.type_ = Posting.Type_Virtual_Balanced
- }
+ [ ( Posting.nil
+ { Posting.account = ["A","B","C"]
+ , Posting.sourcepos = P.newPos "" 1 1
+ }
+ , Posting.Type_Virtual_Balanced
+ )
]
]
, "transaction" ~: TestList
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.transaction <* P.eof)
- Format.Ledger.Read.nil_Context "" "2000/01/01 some description\n A:B:C $1\n a:b:c"])
+ Format.Ledger.Read.nil_Context "" ("2000/01/01 some description\n A:B:C $1\n a:b:c"::Text)])
~?=
[ Transaction.nil
{ Transaction.dates=
, Posting.amounts = Data.Map.fromList
[ ("$", Amount.nil
{ Amount.quantity = 1
- , Amount.style = Style.nil
- { Style.unit_side = Just Style.Side_Left
- , Style.unit_spaced = Just False
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.unit_side = Just Amount.Style.Side_Left
+ , Amount.Style.unit_spaced = Just False
}
, Amount.unit = "$"
})
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.transaction <* P.newline <* P.eof)
- Format.Ledger.Read.nil_Context "" "2000/01/01 some description\n A:B:C $1\n a:b:c\n"])
+ Format.Ledger.Read.nil_Context "" ("2000/01/01 some description\n A:B:C $1\n a:b:c\n"::Text)])
~?=
[ Transaction.nil
{ Transaction.dates=
, Posting.amounts = Data.Map.fromList
[ ("$", Amount.nil
{ Amount.quantity = 1
- , Amount.style = Style.nil
- { Style.unit_side = Just Style.Side_Left
- , Style.unit_spaced = Just False
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.unit_side = Just Amount.Style.Side_Left
+ , Amount.Style.unit_spaced = Just False
}
, Amount.unit = "$"
})
(Data.Either.rights $
[P.runParser
(Format.Ledger.Read.transaction <* P.eof)
- Format.Ledger.Read.nil_Context "" "2000/01/01 some description ; some comment\n ; some other;comment\n; some Tag:\n; some last comment\n A:B:C $1\n a:b:c"])
+ Format.Ledger.Read.nil_Context "" ("2000/01/01 some description ; some comment\n ; some other;comment\n; some Tag:\n; some last comment\n A:B:C $1\n a:b:c"::Text)])
~?=
[ Transaction.nil
{ Transaction.comments_after =
, Posting.amounts = Data.Map.fromList
[ ("$", Amount.nil
{ Amount.quantity = 1
- , Amount.style = Style.nil
- { Style.unit_side = Just Style.Side_Left
- , Style.unit_spaced = Just False
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.unit_side = Just Amount.Style.Side_Left
+ , Amount.Style.unit_spaced = Just False
}
, Amount.unit = "$"
})
jnl <- liftIO $
P.runParserT
(Format.Ledger.Read.journal "" {-<* P.eof-})
- Format.Ledger.Read.nil_Context "" "2000/01/01 1° description\n A:B:C $1\n a:b:c\n2000/01/02 2° description\n A:B:C $1\n x:y:z"
+ Format.Ledger.Read.nil_Context "" ("2000/01/01 1° description\n A:B:C $1\n a:b:c\n2000/01/02 2° description\n A:B:C $1\n x:y:z"::Text)
(Data.List.map
(\j -> j{Format.Ledger.Journal.last_read_time=
Format.Ledger.Journal.last_read_time Format.Ledger.Journal.nil}) $
, Posting.amounts = Data.Map.fromList
[ ("$", Amount.nil
{ Amount.quantity = 1
- , Amount.style = Style.nil
- { Style.unit_side = Just Style.Side_Left
- , Style.unit_spaced = Just False
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.unit_side = Just Amount.Style.Side_Left
+ , Amount.Style.unit_spaced = Just False
}
, Amount.unit = "$"
})
, Posting.amounts = Data.Map.fromList
[ ("$", Amount.nil
{ Amount.quantity = 1
- , Amount.style = Style.nil
- { Style.unit_side = Just Style.Side_Left
- , Style.unit_spaced = Just False
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.unit_side = Just Amount.Style.Side_Left
+ , Amount.Style.unit_spaced = Just False
}
, Amount.unit = "$"
})
]
]
]
+ , "Write" ~: TestList
+ [ "account" ~: TestList
+ [ "nil" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.account Posting.Type_Regular
+ Account.nil)
+ ~?=
+ "")
+ , "A" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.account Posting.Type_Regular
+ ["A"])
+ ~?=
+ "A")
+ , "A:B:C" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.account Posting.Type_Regular
+ ["A", "B", "C"])
+ ~?=
+ "A:B:C")
+ , "(A:B:C)" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.account Posting.Type_Virtual
+ ["A", "B", "C"])
+ ~?=
+ "(A:B:C)")
+ , "[A:B:C]" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.account Posting.Type_Virtual_Balanced
+ ["A", "B", "C"])
+ ~?=
+ "[A:B:C]")
+ ]
+ , "amount" ~: TestList
+ [ "nil" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.amount
+ Amount.nil)
+ ~?=
+ "0")
+ , "nil @ prec=2" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.amount
+ Amount.nil
+ { Amount.style = Amount.Style.nil
+ { Amount.Style.precision = 2 }
+ })
+ ~?=
+ "0.00")
+ , "123" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.amount
+ Amount.nil
+ { Amount.quantity = Decimal 0 123
+ })
+ ~?=
+ "123")
+ , "-123" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.amount
+ Amount.nil
+ { Amount.quantity = Decimal 0 (- 123)
+ })
+ ~?=
+ "-123")
+ , "12.3 @ prec=0" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.amount
+ Amount.nil
+ { Amount.quantity = Decimal 1 123
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ }
+ })
+ ~?=
+ "12")
+ , "12.5 @ prec=0" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.amount
+ Amount.nil
+ { Amount.quantity = Decimal 1 125
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ }
+ })
+ ~?=
+ "13")
+ , "12.3 @ prec=1" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.amount
+ Amount.nil
+ { Amount.quantity = Decimal 1 123
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.precision = 1
+ }
+ })
+ ~?=
+ "12.3")
+ , "1,234.56 @ prec=2" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.amount
+ Amount.nil
+ { Amount.quantity = Decimal 2 123456
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.precision = 2
+ , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
+ }
+ })
+ ~?=
+ "1,234.56")
+ , "123,456,789,01,2.3456789 @ prec=7" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.amount
+ Amount.nil
+ { Amount.quantity = Decimal 7 1234567890123456789
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.precision = 7
+ , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3]
+ }
+ })
+ ~?=
+ "123,456,789,01,2.3456789")
+ , "1234567.8,90,123,456,789 @ prec=12" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.amount
+ Amount.nil
+ { Amount.quantity = Decimal 12 1234567890123456789
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.precision = 12
+ , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3]
+ }
+ })
+ ~?=
+ "1234567.8,90,123,456,789")
+ , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.amount
+ Amount.nil
+ { Amount.quantity = Decimal 7 1234567890123456789
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.precision = 7
+ , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1]
+ }
+ })
+ ~?=
+ "1,2,3,4,5,6,7,89,012.3456789")
+ , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.amount
+ Amount.nil
+ { Amount.quantity = Decimal 12 1234567890123456789
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.precision = 12
+ , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
+ }
+ })
+ ~?=
+ "1234567.890,12,3,4,5,6,7,8,9")
+ ]
+ , "amount_length" ~: TestList
+ [ "nil" ~:
+ ((Format.Ledger.Write.amount_length
+ Amount.nil)
+ ~?=
+ 1)
+ , "nil @ prec=2" ~:
+ ((Format.Ledger.Write.amount_length
+ Amount.nil
+ { Amount.style = Amount.Style.nil
+ { Amount.Style.precision = 2 }
+ })
+ ~?=
+ 4)
+ , "123" ~:
+ ((Format.Ledger.Write.amount_length
+ Amount.nil
+ { Amount.quantity = Decimal 0 123
+ })
+ ~?=
+ 3)
+ , "-123" ~:
+ ((Format.Ledger.Write.amount_length
+ Amount.nil
+ { Amount.quantity = Decimal 0 (- 123)
+ })
+ ~?=
+ 4)
+ , "12.3 @ prec=0" ~:
+ ((Format.Ledger.Write.amount_length
+ Amount.nil
+ { Amount.quantity = Decimal 1 123
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ }
+ })
+ ~?=
+ 2)
+ , "12.5 @ prec=0" ~:
+ ((Format.Ledger.Write.amount_length
+ Amount.nil
+ { Amount.quantity = Decimal 1 125
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ }
+ })
+ ~?=
+ 2)
+ , "12.3 @ prec=1" ~:
+ ((Format.Ledger.Write.amount_length
+ Amount.nil
+ { Amount.quantity = Decimal 1 123
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.precision = 1
+ }
+ })
+ ~?=
+ 4)
+ , "1,234.56 @ prec=2" ~:
+ ((Format.Ledger.Write.amount_length
+ Amount.nil
+ { Amount.quantity = Decimal 2 123456
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.precision = 2
+ , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3]
+ }
+ })
+ ~?=
+ 8)
+ , "123,456,789,01,2.3456789 @ prec=7" ~:
+ ((Format.Ledger.Write.amount_length
+ Amount.nil
+ { Amount.quantity = Decimal 7 1234567890123456789
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.precision = 7
+ , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [1, 2, 3]
+ }
+ })
+ ~?=
+ 24)
+ , "1234567.8,90,123,456,789 @ prec=12" ~:
+ ((Format.Ledger.Write.amount_length
+ Amount.nil
+ { Amount.quantity = Decimal 12 1234567890123456789
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.precision = 12
+ , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [1, 2, 3]
+ }
+ })
+ ~?=
+ 24)
+ , "1,2,3,4,5,6,7,89,012.3456789 @ prec=7" ~:
+ ((Format.Ledger.Write.amount_length
+ Amount.nil
+ { Amount.quantity = Decimal 7 1234567890123456789
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.precision = 7
+ , Amount.Style.grouping_integral = Just $ Amount.Style.Grouping ',' [3, 2, 1]
+ }
+ })
+ ~?=
+ 28)
+ , "1234567.890,12,3,4,5,6,7,8,9 @ prec=12" ~:
+ ((Format.Ledger.Write.amount_length
+ Amount.nil
+ { Amount.quantity = Decimal 12 1234567890123456789
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.fractioning = Just '.'
+ , Amount.Style.precision = 12
+ , Amount.Style.grouping_fractional = Just $ Amount.Style.Grouping ',' [3, 2, 1]
+ }
+ })
+ ~?=
+ 28)
+ ]
+ , "date" ~: TestList
+ [ "nil" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.date
+ Date.nil)
+ ~?=
+ "1970/01/01")
+ , "2000/01/01 12:34:51 CET" ~:
+ (Format.Ledger.Write.show $
+ Format.Ledger.Write.date $
+ Time.ZonedTime
+ (Time.LocalTime
+ (Time.fromGregorian 2000 01 01)
+ (Time.TimeOfDay 12 34 51))
+ (Time.TimeZone 60 False "CET"))
+ ~?=
+ "2000/01/01 12:34:51 CET"
+ , "2000/01/01 12:34:51 +0100" ~:
+ (Format.Ledger.Write.show $
+ Format.Ledger.Write.date $
+ Time.ZonedTime
+ (Time.LocalTime
+ (Time.fromGregorian 2000 01 01)
+ (Time.TimeOfDay 12 34 51))
+ (Time.TimeZone 60 False ""))
+ ~?=
+ "2000/01/01 12:34:51 +0100"
+ , "2000/01/01 01:02:03" ~:
+ (Format.Ledger.Write.show $
+ Format.Ledger.Write.date $
+ Time.ZonedTime
+ (Time.LocalTime
+ (Time.fromGregorian 2000 01 01)
+ (Time.TimeOfDay 1 2 3))
+ (Time.utc))
+ ~?=
+ "2000/01/01 01:02:03"
+ , "01/01 01:02" ~:
+ (Format.Ledger.Write.show $
+ Format.Ledger.Write.date $
+ Time.ZonedTime
+ (Time.LocalTime
+ (Time.fromGregorian 0 01 01)
+ (Time.TimeOfDay 1 2 0))
+ (Time.utc))
+ ~?=
+ "01/01 01:02"
+ , "01/01 01:00" ~:
+ (Format.Ledger.Write.show $
+ Format.Ledger.Write.date $
+ Time.ZonedTime
+ (Time.LocalTime
+ (Time.fromGregorian 0 01 01)
+ (Time.TimeOfDay 1 0 0))
+ (Time.utc))
+ ~?=
+ "01/01 01:00"
+ , "01/01 00:01" ~:
+ (Format.Ledger.Write.show $
+ Format.Ledger.Write.date $
+ Time.ZonedTime
+ (Time.LocalTime
+ (Time.fromGregorian 0 01 01)
+ (Time.TimeOfDay 0 1 0))
+ (Time.utc))
+ ~?=
+ "01/01 00:01"
+ , "01/01" ~:
+ (Format.Ledger.Write.show $
+ Format.Ledger.Write.date $
+ Time.ZonedTime
+ (Time.LocalTime
+ (Time.fromGregorian 0 01 01)
+ (Time.TimeOfDay 0 0 0))
+ (Time.utc))
+ ~?=
+ "01/01"
+ ]
+ , "transaction" ~: TestList
+ [ "nil" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.transaction
+ Transaction.nil)
+ ~?=
+ "1970/01/01\n")
+ , "2000/01/01 some description\\n\\ta:b:c\\n\\t\\t; first comment\\n\\t\\t; second comment\\n\\t\\t; third comment\\n\\tA:B:C $1" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.transaction $
+ Transaction.nil
+ { Transaction.dates=
+ ( Time.ZonedTime
+ (Time.LocalTime
+ (Time.fromGregorian 2000 01 01)
+ (Time.TimeOfDay 0 0 0))
+ (Time.utc)
+ , [] )
+ , Transaction.description="some description"
+ , Transaction.postings = Posting.from_List
+ [ Posting.nil
+ { Posting.account = ["A","B","C"]
+ , Posting.amounts = Data.Map.fromList
+ [ ("$", Amount.nil
+ { Amount.quantity = 1
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.unit_side = Just Amount.Style.Side_Left
+ , Amount.Style.unit_spaced = Just False
+ }
+ , Amount.unit = "$"
+ })
+ ]
+ }
+ , Posting.nil
+ { Posting.account = ["a","b","c"]
+ , Posting.comments = ["first comment","second comment","third comment"]
+ }
+ ]
+ })
+ ~?=
+ "2000/01/01 some description\n\ta:b:c\n\t\t; first comment\n\t\t; second comment\n\t\t; third comment\n\tA:B:C $1")
+ , "2000/01/01 some description\\n\\tA:B:C $1\\n\\tAA:BB:CC $123" ~:
+ ((Format.Ledger.Write.show $
+ Format.Ledger.Write.transaction $
+ Transaction.nil
+ { Transaction.dates=
+ ( Time.ZonedTime
+ (Time.LocalTime
+ (Time.fromGregorian 2000 01 01)
+ (Time.TimeOfDay 0 0 0))
+ (Time.utc)
+ , [] )
+ , Transaction.description="some description"
+ , Transaction.postings = Posting.from_List
+ [ Posting.nil
+ { Posting.account = ["A","B","C"]
+ , Posting.amounts = Data.Map.fromList
+ [ ("$", Amount.nil
+ { Amount.quantity = 1
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.unit_side = Just Amount.Style.Side_Left
+ , Amount.Style.unit_spaced = Just False
+ }
+ , Amount.unit = "$"
+ })
+ ]
+ }
+ , Posting.nil
+ { Posting.account = ["AA","BB","CC"]
+ , Posting.amounts = Data.Map.fromList
+ [ ("$", Amount.nil
+ { Amount.quantity = 123
+ , Amount.style = Amount.Style.nil
+ { Amount.Style.unit_side = Just Amount.Style.Side_Left
+ , Amount.Style.unit_spaced = Just False
+ }
+ , Amount.unit = "$"
+ })
+ ]
+ }
+ ]
+ })
+ ~?=
+ "2000/01/01 some description\n\tA:B:C $1\n\tAA:BB:CC $123")
+ ]
+ ]
]
]
]