summaryrefslogtreecommitdiff
path: root/Hledger
diff options
context:
space:
mode:
Diffstat (limited to 'Hledger')
-rw-r--r--Hledger/JournalCSVs.hs41
-rw-r--r--Hledger/RegisterCSV.hs64
2 files changed, 46 insertions, 59 deletions
diff --git a/Hledger/JournalCSVs.hs b/Hledger/JournalCSVs.hs
index 1d5ac5f..f70b8a5 100644
--- a/Hledger/JournalCSVs.hs
+++ b/Hledger/JournalCSVs.hs
@@ -15,32 +15,34 @@
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE OverloadedStrings #-}
module Hledger.JournalCSVs (pAndL, assets, liabilities, everything, JReportType(..)) where
-import Prelude (Enum(..), String, Integer, Int, Eq, Show, (.), ($), (*), (+), (++), (==), (&&), (>>=), (=<<), const, div, length, lookup, map, mod, subtract, filter, flip, fromIntegral, fst, return, snd, head, last, error, uncurry, Maybe(..), Bool(..), Either(..), IO, FilePath, Read)
+import Prelude (Enum(..), Integer, Int, Eq, Show, (.), ($), (*), (+), (++), (==), (>>=), (=<<), const, div, lookup, map, mod, subtract, flip, fromIntegral, fst, return, snd, head, last, error, uncurry, Maybe(..), Bool(..), Either(..), IO, FilePath, Read)
import Control.Applicative (liftA2)
import Control.Monad (ap, when)
-import Data.Conduit (($$), ($=))
+import Data.Conduit (runConduit, (.|))
import qualified Data.Conduit.List as CL
import Data.CSV.Conduit (fromCSV, defCSVSettings, runResourceT)
-import Data.List (nub, sort, sortBy, isPrefixOf, intercalate)
-import Data.List.Split (splitOn)
+import Data.List (nub, sort, sortBy)
import Data.Maybe (fromMaybe)
import Data.Ord (comparing)
import qualified Data.Text as T
import Data.Time.Calendar (fromGregorian, toGregorian, Day(..))
import Data.Time.Format (formatTime)
-import Data.Tree (Tree(..))
-import System.Locale (defaultTimeLocale)
+import Data.Time.Format (defaultTimeLocale)
import Hledger.Data.Amount (showMixedAmount)
import Hledger.Data.Journal (journalProfitAndLossAccountQuery, journalAssetAccountQuery, journalLiabilityAccountQuery)
-import Hledger.Data.Types (DateSpan(..), Journal(..), Transaction(..))
+import Hledger.Data.Types (DateSpan(..), Journal(..), Transaction(..), MixedAmount (..))
import Hledger.Query (Query(..))
-import Hledger.Read (readJournalFile)
+import Hledger.Read (readJournalFile, definputopts)
import Hledger.Reports (balanceReport, defreportopts, ReportOpts(..))
+showMixedAmountT :: MixedAmount -> T.Text
+showMixedAmountT = T.pack . showMixedAmount
+
data JReportType = PandL | Assets | Liabilities | Everything
deriving (Eq, Read, Show)
@@ -57,7 +59,7 @@ everything :: FilePath -> IO T.Text
everything fn = fn2CSV (const Any) fn
fn2CSV :: (Journal -> Query) -> FilePath -> IO T.Text
-fn2CSV q fn = readJournalFile Nothing Nothing fn >>= \(Right j) -> jToCSV True j (q j)
+fn2CSV q fn = readJournalFile definputopts fn >>= \(Right j) -> jToCSV True j (q j)
-- sign-change Income lines
@@ -84,12 +86,13 @@ jToCSV delta jnl q = do
when (firstMonth == lastMonth) $ error "Need multiple months"
let reports = map (\m -> balanceReport defreportopts { no_elide_ = True } (q' m) jnl) [firstMonth..lastMonth]
reportT = balanceReport defreportopts { no_elide_ = True } Any jnl
- reports' = map (map (\((n, _, _), a) -> (n, showMixedAmount a)) . fst) reports
- reportT' = (map (\((n, _, _), a) -> (n, showMixedAmount a)) . fst) reportT
+ reports' = map (map (\(n, _, _, a) -> (n, showMixedAmountT a)) . fst) reports
+ reportT' = (map (\(n, _, _, a) -> (n, showMixedAmountT a)) . fst) reportT
allaccounts = sort . nub . (map fst =<<) $ reports'
concordant = map (\x -> x : fetchSeries reports' x ++ fetchSeries [reportT'] x) allaccounts
- withheader = ("Account":map (formatTime defaultTimeLocale "%b of %Y" . yearMonthToDay) [firstMonth..lastMonth] ++ ["Period Total"]):concordant
- c <- runResourceT $ CL.sourceList withheader $= CL.map (map T.pack) $= fromCSV defCSVSettings $$ CL.consume
+ withheader = ("Account":map (T.pack . formatTime defaultTimeLocale "%b of %Y" . yearMonthToDay) [firstMonth..lastMonth] ++ ["Period Total"]):concordant
+ c <- runResourceT . runConduit $
+ CL.sourceList withheader .| fromCSV defCSVSettings .| CL.consume
return $ T.concat c
dS :: Bool -> YearMonth -> DateSpan
@@ -98,15 +101,5 @@ dS delta (YearMonth (y,m)) = DateSpan (if delta then Just startD else Nothing) (
startD = fromGregorian y m 01
endD = fromGregorian y m 31
-fetchSeries :: [[(String, String)]] -> String -> [String]
+fetchSeries :: [[(T.Text, T.Text)]] -> T.Text -> [T.Text]
fetchSeries rs a = map (fromMaybe "$0.00" . lookup a) rs
-
-chirren :: [String] -> [[String]] -> [[String]]
-chirren p = filter (\x -> length x == (length p + 1) && isPrefixOf p x)
-
-accts2Tree :: [[String]] -> Tree String
-accts2Tree as = Node "" (subtrees [])
- where
- subtrees xs = map (\x -> Node (colonize x) (subtrees x)) (chirren xs as)
- colonize = intercalate ":"
-
diff --git a/Hledger/RegisterCSV.hs b/Hledger/RegisterCSV.hs
index 69fec77..dd5ee6c 100644
--- a/Hledger/RegisterCSV.hs
+++ b/Hledger/RegisterCSV.hs
@@ -15,30 +15,25 @@
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE OverloadedStrings #-}
module Hledger.RegisterCSV (convertJournalToRegisterCSV) where
-import Prelude (String, Double, Show, Eq, (||), Bool(..), const, (<), (>), snd, (.), ($), maybe, show, id, length, (==), (/=), head, map, FilePath, IO, Either(..), Maybe(..), return, concatMap, Char, otherwise)
+import Prelude (String, Double, Show, Eq, (||), Bool(..), const, (<), (>), snd, (.), ($), maybe, show, id, length, (==), (/=), head, map, FilePath, IO, Either(..), return, concatMap, Char, otherwise)
import Control.Applicative (many)
-import Control.Monad.IO.Class (MonadIO)
-import Control.Monad.Trans.Control (MonadBaseControl)
-import Control.Monad.Trans.Resource (MonadThrow)
-import Control.Monad.Primitive (PrimMonad)
-import Control.Monad.Base (MonadBase)
-import Data.List (isPrefixOf)
import qualified Data.Text as T
import Hledger.Data.Amount (showMixedAmount)
import Hledger.Data.Journal (journalAccountNamesUsed)
import Hledger.Data.Types (Journal(..), Transaction(..), Posting(..), MixedAmount(..))
import Hledger.Query (Query(..))
-import Hledger.Read (readJournalFile)
+import Hledger.Read (readJournalFile, definputopts)
import Hledger.Reports (postingsReport, defreportopts, PostingsReportItem)
-import Data.Conduit (($=),($$))
-import Control.Monad.Trans.Resource (runResourceT)
+import Data.Conduit (runConduit, (.|))
+import Control.Monad.Trans.Resource (MonadUnliftIO (), runResourceT)
import qualified Data.Conduit.List as CL
import Data.CSV.Conduit (fromCSV, defCSVSettings, CSV)
@@ -47,27 +42,29 @@ import Text.Parsec.Combinator (many1)
import Text.Parsec.Prim (ParsecT, Stream, parse)
data AcctReg = AcctReg {
- _acct :: String
+ _acct :: T.Text
, _openingBalance :: Double
, _items :: [PostingsReportItem]
} deriving (Show, Eq)
-cordGuess :: String -> MixedAmount -> T.Text
+cordGuess :: T.Text -> MixedAmount -> T.Text
cordGuess acct
- | "Assets:" `isPrefixOf` acct || "Liabilities:" `isPrefixOf` acct || "Equity:" `isPrefixOf` acct = cordGuest' True
- | "Income:" `isPrefixOf` acct || "Expenses:" `isPrefixOf` acct = cordGuest' False
- | otherwise = const (T.pack "INVALID")
+ | "Assets:" `T.isPrefixOf` acct || "Liabilities:" `T.isPrefixOf` acct || "Equity:" `T.isPrefixOf` acct = cordGuest' True
+ | "Income:" `T.isPrefixOf` acct || "Expenses:" `T.isPrefixOf` acct = cordGuest' False
+ | otherwise = const "INVALID"
where
- cordGuest' True amt | amt > 0 = T.pack "Deposit"
- cordGuest' True _ = T.pack "Check"
- cordGuest' False amt | amt > 0 = T.pack "Check"
- cordGuest' False _ = T.pack "Deposit"
+ cordGuest' True amt | amt > 0 = "Deposit"
+ cordGuest' True _ = "Check"
+ cordGuest' False amt | amt > 0 = "Check"
+ cordGuest' False _ = "Deposit"
-acctReg :: String -> Journal -> AcctReg
-acctReg a j = AcctReg a 0 (snd . postingsReport defreportopts (Acct a) $ j)
+acctReg :: T.Text -> Journal -> AcctReg
+acctReg a j = AcctReg a 0 (snd . postingsReport defreportopts (Acct . T.unpack $ a) $ j)
+
+-- (Maybe Day, Maybe Day, Maybe String, Posting, MixedAmount)
priToLine :: PostingsReportItem -> [T.Text]
-priToLine (mday, mdesc, p, mixa) = [T.empty, cord, date, num, name, memo, split, amt, bal]
+priToLine (mday, _, mdesc, p, mixa) = [T.empty, cord, date, num, name, memo, split, amt, bal]
where
date = maybe T.empty (T.pack . show) mday
desc' = maybe "" id mdesc
@@ -82,32 +79,29 @@ priToLine (mday, mdesc, p, mixa) = [T.empty, cord, date, num, name, memo, split,
splitField :: [Posting] -> T.Text
splitField ps
- | length ps < 2 = T.pack "ERROR"
- | length ps == 2 = T.pack (paccount . head $ ps)
- | otherwise = T.pack "-SPLIT-"
+ | length ps < 2 = "ERROR"
+ | length ps == 2 = paccount . head $ ps
+ | otherwise = "-SPLIT-"
arToLines :: AcctReg -> [[T.Text]]
-arToLines ar = [T.pack . _acct $ ar,T.empty,T.empty,T.empty,T.empty,T.empty,T.empty,T.empty,T.pack "0.000000"]:map priToLine (_items ar)
+arToLines ar = [_acct ar,"","","","","","","","0.000000"]:map priToLine (_items ar)
convertJournalToRegisterCSV :: FilePath -> IO (T.Text)
convertJournalToRegisterCSV fp = do
- Right j <- readJournalFile Nothing Nothing fp
+ Right j <- readJournalFile definputopts fp
csv <- journalToRegisterCSV j
return $ T.concat csv
-journalToRegisterCSV :: ( PrimMonad base,
- MonadBase base m,
- MonadThrow m,
- MonadIO m,
- CSV a [T.Text],
- MonadBaseControl IO m)
+journalToRegisterCSV :: ( MonadUnliftIO m
+ , CSV a [T.Text])
=> Journal
-> m [a]
journalToRegisterCSV j = do
let accts = journalAccountNamesUsed j
precsv' = concatMap (\x -> arToLines $ acctReg x j) accts
- precsv = [T.empty, T.pack "Type",T.pack "Date",T.pack "Num",T.pack "Name",T.pack "Memo",T.pack "Split",T.pack "Amount",T.pack "Balance"]:precsv'
- csv <- runResourceT $ CL.sourceList precsv $= fromCSV defCSVSettings $$ CL.consume
+ precsv = ["","Type","Date","Num","Name","Memo","Split","Amount","Balance"]:precsv'
+ csv <- runResourceT . runConduit $
+ CL.sourceList precsv .| fromCSV defCSVSettings .| CL.consume
return csv
parseDesc :: String -> (String, String)