module Hcompta.LCC.Write.Compta where import Control.Monad (Monad(..)) import Data.Bool import Data.Char (Char) import Data.Decimal import Data.Eq (Eq(..)) import Data.Foldable (Foldable(..)) import Data.Function (($), (.), flip, id) import Data.Functor ((<$>)) import Data.Functor.Compose (Compose(..)) import Data.Maybe (Maybe(..), fromMaybe) import Data.Monoid (Monoid(..)) import Data.Ord (Ord(..)) import Data.Semigroup (Semigroup(..)) import Data.Tuple (fst, uncurry) import GHC.Exts (Int(..)) import Prelude (Integer, Num(..), RealFrac(..), Show(..), Integral(..), fromIntegral, toInteger) import System.IO (IO) import qualified Data.ByteString as BS import qualified Data.Char as Char import qualified Data.List as List import qualified Data.Map.Strict as Map import qualified Data.MonoTraversable as MT import qualified Data.NonNull as NonNull import qualified Data.Strict as S import qualified Data.Text as T import qualified Data.Text.Encoding as Enc import qualified Data.TreeMap.Strict as TreeMap import qualified Language.Symantic.Document.Term.Dimension as Dim import qualified Language.Symantic.Document as D import qualified Language.Symantic.Grammar as G import qualified Language.Symantic as Sym import qualified Hcompta as H import Hcompta.LCC.Account import Hcompta.LCC.Amount import Hcompta.LCC.Chart import Hcompta.LCC.IO import Hcompta.LCC.Journal import Hcompta.LCC.Name import Hcompta.LCC.Posting import Hcompta.LCC.Tag import Hcompta.LCC.Transaction import Hcompta.LCC.Source import Hcompta.LCC.Compta import qualified Hcompta.LCC.Read.Compta as G -- * Class 'Writeable' class Writeable d a where write :: a -> d widthWrite :: Writeable Dim.Dimension a => a -> Int widthWrite a = case Dim.dim_width $ Dim.dim $ write a of D.Nat i -> fromInteger i -- import Debug.Trace (trace) -- dbg msg x = trace (msg <> " = " <> show x) x -- * Type 'Reader' data Reader = Reader { reader_account_ref :: Bool , reader_amounts :: Style_Amounts , reader_width_acct_amt :: Int } inh :: Reader inh = Reader { reader_account_ref = True , reader_amounts = Style_Amounts Map.empty , reader_width_acct_amt = 0 } instance (D.Textable d, D.Colorable d, D.Indentable d) => Writeable d Date where write dat = let (y, mo, d) = H.gregorianOf dat in (if y == 0 then D.empty else D.integer y <> sep G.char_ymd_sep) <> int2 mo <> sep G.char_ymd_sep <> int2 d <> (case H.todOf dat of (0, 0, 0) -> D.empty (h, m, s) -> sep '_' <> int2 h <> sep ':' <> int2 m <> (case s of 0 -> D.empty _ -> sep ':' <> (if s < 10 then D.charH '0' else D.empty) <> D.integer ((truncate s::Integer)))) where int2 i = (if i < 10 then D.charH '0' else D.empty) <> D.int i sep = D.blacker . D.charH instance (D.Textable d, D.Colorable d, D.Indentable d, Monoid d) => Writeable d Account where write acct = (`MT.ofoldMap` acct) $ \a -> D.blacker (D.charH G.char_account_sep) <> write a instance D.Textable d => Writeable d NameAccount where write = D.textH . unName instance (D.Textable d, D.Colorable d, D.Indentable d) => Writeable d Tag_Path where write (Tag_Path path) = D.catH $ (:) (D.yellower $ D.charH G.char_account_tag_prefix) $ List.intersperse (D.yellower $ D.charH G.char_tag_sep) (D.textH . unName <$> NonNull.toNullable path) instance (D.Textable d, D.Colorable d, D.Indentable d) => Writeable d Account_Tag where write (Account_Tag (Tag (Tag_Path path) (Tag_Data value))) = D.catH ( (:) (D.yellower $ D.charH G.char_account_tag_prefix) $ List.intersperse (D.yellower $ D.charH G.char_tag_sep) (D.textH . unName <$> NonNull.toNullable path) ) <> if T.null value then D.empty else D.yellower (D.charH G.char_tag_data_prefix) <> D.textH value instance (D.Textable d, D.Colorable d, D.Indentable d, D.Decorable d) => Writeable d (Styled_Amount Amount) where write ( sty@Style_Amount { style_amount_unit_side = uside , style_amount_unit_spaced = uspaced } , Amount u q ) = case uside of S.Just L -> write u <> case uspaced of S.Just True | not (H.null u) -> D.space _ -> D.empty _ -> D.empty <> write (sty, q) <> case uside of S.Just R -> (case uspaced of S.Just True | not (H.null u) -> D.space _ -> D.empty) <> write u S.Nothing -> (case uspaced of S.Just True | not (H.null u) -> D.space _ -> D.empty) <> write u _ -> D.empty instance (D.Textable d, D.Colorable d, D.Indentable d, D.Decorable d) => Writeable (Reader -> d) Amount where write amt ro = write (styled_amount (reader_amounts ro) amt) instance (D.Textable d, D.Colorable d, D.Indentable d, D.Decorable d, Monoid d) => Writeable (Reader -> d) Amounts where write (Amounts amts) ro = mconcat $ List.intersperse " + " $ ((`write` ro) <$>) $ uncurry Amount <$> Map.toList amts instance (D.Textable d, D.Colorable d, D.Indentable d, D.Decorable d) => Writeable d Unit where write (Unit t) = D.yellower $ if T.all (\c -> case Char.generalCategory c of Char.CurrencySymbol -> True Char.LowercaseLetter -> True Char.ModifierLetter -> True Char.OtherLetter -> True Char.TitlecaseLetter -> True Char.UppercaseLetter -> True _ -> False ) t then D.textH t else D.between (D.charH '"') (D.charH '"') $ D.textH t instance (D.Textable d, D.Colorable d, D.Indentable d, D.Decorable d) => Writeable d (Styled_Amount Quantity) where write ( Style_Amount { style_amount_fractioning , style_amount_grouping_integral , style_amount_grouping_fractional } , qty ) = do let Decimal e n = qty let num = show $ abs n let sign = D.bold $ D.yellower $ D.textH (if n < 0 then "-" else "") if e == 0 then sign <> D.bold (D.blue $ D.stringH num) else do let num_len = List.length num let padded = List.concat [ List.replicate (fromIntegral e + 1 - num_len) '0' , num -- , replicate (fromIntegral precision - fromIntegral e) '0' ] let (int, frac) = List.splitAt (max 1 (num_len - fromIntegral e)) padded let default_fractioning = List.head $ del_grouping_sep style_amount_grouping_integral $ del_grouping_sep style_amount_grouping_fractional $ ['.', ','] sign <> D.bold (D.blue $ D.stringH (S.maybe id (\g -> List.reverse . group g . List.reverse) style_amount_grouping_integral $ int) <> D.yellower (D.charH (S.fromMaybe default_fractioning style_amount_fractioning)) <> D.stringH (S.maybe id group style_amount_grouping_fractional frac)) where group :: Style_Amount_Grouping -> [Char] -> [Char] group (Style_Amount_Grouping sep sizes_) = List.concat . List.reverse . List.map List.reverse . fst . List.foldl' (flip (\digit x -> case x of ([], sizes) -> ([[digit]], sizes) (digits:groups, []) -> ((digit:digits):groups, []) (digits:groups, curr_sizes@(size:sizes)) -> if List.length digits < size then ( (digit:digits):groups, curr_sizes) else ([digit]:[sep]:digits:groups, if List.null sizes then curr_sizes else sizes) )) ([], sizes_) del_grouping_sep grouping = case grouping of S.Just (Style_Amount_Grouping sep _) -> List.delete sep _ -> id instance (D.Textable d, D.Colorable d, D.Indentable d) => Writeable d Comment where write (Comment com) = D.cyan $ D.charH G.char_comment_prefix <> (case T.uncons com of Just (c, _) | not $ Char.isSpace c -> D.space _ -> D.empty) <> D.textH com instance (D.Textable d, D.Colorable d, D.Indentable d) => Writeable d (d, [Comment]) where write (prefix, com) = D.catH $ List.intersperse D.newline $ (\c -> prefix <> write c) <$> com instance (D.Textable d, D.Colorable d, D.Indentable d, D.Decorable d, Monoid d) => Writeable d (Reader, Posting src) where write (ro, Posting { posting_account , posting_account_ref , posting_amounts , posting_comments -- , posting_dates -- , posting_tags }) = let d_indent = D.spaces 2 in d_indent <> let (d_acct, w_acct) = case posting_account_ref of S.Just (a S.:!: sa) | reader_account_ref ro -> ( write a <> S.maybe D.empty write sa , widthWrite a + S.maybe 0 widthWrite sa ) _ -> (write posting_account, widthWrite posting_account) in (case posting_amounts of Amounts amts | Map.null amts -> d_acct Amounts amts -> fromMaybe D.empty $ Map.foldlWithKey (\mdoc unit qty -> Just $ let amt = styled_amount (reader_amounts ro) $ Amount unit qty in let pad = max 0 $ reader_width_acct_amt ro - (w_acct + widthWrite amt) in (case mdoc of Nothing -> D.empty Just doc -> doc <> D.newline <> d_indent) <> d_acct <> D.stringH ( List.replicate (pad) '_') <> D.space <> write amt <> D.space <> D.stringH (show (reader_width_acct_amt ro, w_acct, widthWrite amt)) ) Nothing amts) <> (case posting_comments of [] -> D.empty [c] -> D.space <> write c _ -> D.newline <> write (d_indent <> D.space :: d, posting_comments)) instance (D.Textable d, D.Colorable d, D.Indentable d, D.Decorable d, Monoid d) => Writeable d (Reader, Transaction src) where write (ro, txn@Transaction { transaction_comments , transaction_dates , transaction_wording = Wording transaction_wording , transaction_postings = Postings transaction_postings , transaction_tags = Transaction_Tags (Tags tags) }) = D.catH ( List.intersperse (D.charH G.char_transaction_date_sep) (write <$> NonNull.toNullable transaction_dates)) <> (case transaction_wording of "" -> D.empty _ -> D.space <> D.magenta (D.textH transaction_wording)) <> D.newline <> (case transaction_comments of [] -> D.empty _ -> write (D.space :: d, transaction_comments) <> D.newline) <> TreeMap.foldrWithPath (\path -> flip $ foldr (\value -> (<>) (D.spaces 2 <> write (Transaction_Tag (Tag (Tag_Path path) value)) <> D.newline))) D.empty tags <> D.catV (write . (ro',) <$> Compose transaction_postings) where ro' = ro { reader_width_acct_amt = case reader_width_acct_amt ro of 0 -> w_Transaction ro txn w -> w } instance (D.Textable d, D.Colorable d, D.Indentable d, D.Decorable d, Monoid d) => Writeable d (Reader, Transactions src) where write (ro, Transactions txns) = let ro' = ro{reader_width_acct_amt = foldr (max . w_Transaction ro) 0 $ Compose txns} in fromMaybe D.empty $ foldl (\mdoc txn -> Just $ write (ro', txn) <> case mdoc of Nothing -> D.newline Just doc -> D.newline <> D.newline <> doc ) Nothing (Compose txns) instance (D.Textable d, D.Colorable d, D.Indentable d, D.Decorable d, Monoid d) => Writeable d Transaction_Tag where write (Transaction_Tag (Tag (Tag_Path path) (Tag_Data value))) = D.catH ( (:) (D.yellower $ D.charH G.char_tag_prefix) $ List.intersperse (D.yellower $ D.charH G.char_tag_sep) (D.bold . D.textH . unName <$> NonNull.toNullable path)) <> if T.null value then D.empty else D.yellower (D.charH G.char_tag_data_prefix) <> D.textH value instance (D.Textable d, D.Colorable d, D.Indentable d, D.Decorable d, Monoid d, Writeable d (ro, j)) => Writeable d (ro, Journal src j) where write (ro, Journal { journal_content , journal_terms , journal_chart }) = (if null journal_terms then D.empty else (write journal_terms <> D.newline)) <> (if H.null journal_chart then D.empty else (write journal_chart <> D.newline)) <> write (ro, journal_content) instance (D.Textable d, D.Colorable d, D.Indentable d, D.Decorable d, Monoid d, Writeable d (ro, j)) => Writeable d (ro, Journals src j) where write (ro, Journals js) = Map.foldl (\doc j@Journal{journal_file=PathFile jf} -> doc <> write (Comment $ T.pack jf) <> D.newline <> D.newline <> write (ro, j) ) D.empty js instance (D.Textable d, D.Colorable d, D.Indentable d, D.Decorable d, Monoid d) => Writeable d Chart where write = TreeMap.foldlWithPath (\doc acct (Account_Tags (Tags ca)) -> doc <> write (H.to acct :: Account) <> D.newline <> TreeMap.foldlWithPath (\doc' tp tvs -> doc' <> foldl' (\doc'' tv -> doc'' <> D.spaces 2 <> write (Account_Tag (Tag (Tag_Path tp) tv)) <> D.newline) D.empty tvs) D.empty ca ) D.empty . chart_accounts instance (D.Textable d, D.Colorable d, D.Indentable d, D.Decorable d, Monoid d) => Writeable d (Terms src) where write = Map.foldlWithKey (\doc n (G.At _src t) -> doc <> write n <> D.space <> D.text t <> D.newline) D.empty instance (D.Textable d, D.Colorable d, D.Indentable d) => Writeable d (Sym.Mod Sym.NameTe) where write (ms `Sym.Mod` Sym.NameTe n) = D.catH $ List.intersperse (D.charH '.') $ ((\(Sym.NameMod m) -> D.textH m) <$> ms) <> [(if isOp n then id else D.yellower) $ D.text n] where isOp = T.all $ \case '_' -> True; '\'' -> True; c -> Char.isAlphaNum c instance (D.Textable d, D.Colorable d, D.Indentable d, D.Decorable d, Monoid d) => Writeable d (Reader, LCC src) where write (ro, LCC { lcc_journals = js , lcc_style = amts }) = write (ro{reader_amounts = reader_amounts ro <> amts}, js) instance (D.Textable d, D.Colorable d, D.Indentable d, D.Decorable d, Monoid d) => Writeable (Reader -> d) (LCC src) where write LCC { lcc_journals = js , lcc_style = amts } ro = write (ro{reader_amounts = reader_amounts ro <> amts}, js) {- instance (D.Textable d, D.Colorable d, D.Indentable d, D.Decorable d, Monoid d, Writeable d (Reader, j)) => Writeable d (Reader, Compta src ss j) where write (ro, Compta { compta_journals = js , compta_chart = c@Chart{chart_accounts=ca} , compta_style_amounts = amts , compta_terms = terms }) = (if null terms then D.empty else (write terms <> D.newline)) <> (if TreeMap.null ca then D.empty else (write c <> D.newline)) <> write (ro{reader_amounts = reader_amounts ro <> amts}, js) -} instance (D.Textable d, D.Colorable d, D.Indentable d, D.Decorable d) => Writeable (IO d) SourcePos where write (SourcePos p (PosFile l) (PosFile c)) = do content <- Enc.decodeUtf8 <$> BS.readFile p let ls = T.lines content let ll = max 1 $ l - size_ctx let qs = List.take (intFrom $ (l - ll) + 1 + size_ctx) $ List.drop (intFrom $ ll-1) ls let ns = show <$> List.take (List.length qs) [ll..] let max_len_n = maximum $ 0 : (List.length <$> ns) let ns' = (<$> ns) $ \n -> List.replicate (max_len_n - List.length n) ' ' <> n let quote = D.catV $ List.zipWith (\(n, sn) q -> D.spaces 2 <> D.blacker (D.stringH sn) <> D.spaces 2 <> (if n == l then mark q else D.textH q) ) (List.zip [ll..] ns') qs return $ quote <> D.newline where size_ctx = 2 intFrom = fromInteger . toInteger mark q = let (b, a) = T.splitAt (intFrom c - 1) q in D.textH b <> case T.uncons a of Nothing -> D.red D.space Just (a0, a') -> D.red (D.charH a0) <> D.textH a' -- | Return the width of given 'Postings', -- considering only 'Account's and 'Amount's (not indentation, 'Comment's, nor 'Posting_Tag's). w_Transaction :: Reader -> Transaction src -> Int -- w_Postings ro = MT.ofoldr (max . widthWrite ro) 0 w_Transaction ro = MT.ofoldr (\Posting { posting_account , posting_account_ref , posting_amounts } -> max $ let w_Acct = case posting_account_ref of S.Just (a S.:!: sa) | reader_account_ref ro -> widthWrite a + S.maybe 0 widthWrite sa _ -> widthWrite posting_account in let w_Amt = case posting_amounts of Amounts amts | Map.null amts -> 0 Amounts amts -> Map.foldrWithKey (\unit qty -> max $ let amt = styled_amount (reader_amounts ro) $ Amount unit qty in widthWrite amt) 1 amts in w_Acct + w_Amt ) 0 . transaction_postings