diff options
Diffstat (limited to 'Hledger/JournalCSVs.hs')
-rw-r--r-- | Hledger/JournalCSVs.hs | 41 |
1 files changed, 17 insertions, 24 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 ":" - |