diff options
author | Clint Adams <clint@softwarefreedom.org> | 2013-04-22 17:41:15 -0400 |
---|---|---|
committer | Clint Adams <clint@softwarefreedom.org> | 2013-04-22 17:41:15 -0400 |
commit | f1a294e5ddb8ae0ccdcef1a12561e603ff996cfe (patch) | |
tree | 14d4df6383db09051ef9631dbf09c9ed6a2039d3 /Hledger | |
parent | 514ff2acff2ba9ad9f809e22fc8ed5a986410e5d (diff) |
journal-query-based monthly reports (p&l, assets, liabilities)
Diffstat (limited to 'Hledger')
-rw-r--r-- | Hledger/JournalCSVs.hs | 113 |
1 files changed, 113 insertions, 0 deletions
diff --git a/Hledger/JournalCSVs.hs b/Hledger/JournalCSVs.hs new file mode 100644 index 0000000..b7d5420 --- /dev/null +++ b/Hledger/JournalCSVs.hs @@ -0,0 +1,113 @@ +-- sflc-ledger-reports: web interface to hledger-based reports +-- Copyright (C) 2013 Clint Adams +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU Affero General Public License as +-- published by the Free Software Foundation, either version 3 of the +-- License, or (at your option) any later version. +-- +-- This program is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU Affero General Public License for more details. +-- +-- You should have received a copy of the GNU Affero General Public License +-- along with this program. If not, see <http://www.gnu.org/licenses/>. + +{-# LANGUAGE FlexibleContexts #-} + +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 Control.Applicative (liftA2) +import Control.Monad (ap, when) +import Data.Conduit (($$), ($=)) +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.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 Hledger.Data.Amount (showMixedAmount) +import Hledger.Data.Journal (journalProfitAndLossAccountQuery, journalAssetAccountQuery, journalLiabilityAccountQuery) +import Hledger.Data.Types (DateSpan(..), Journal(..), Transaction(..)) +import Hledger.Query (Query(..)) +import Hledger.Read (readJournalFile) +import Hledger.Reports (accountsReport, defreportopts, ReportOpts(..)) + +data JReportType = PandL | Assets | Liabilities | Everything + deriving (Eq, Read, Show) + +pAndL :: FilePath -> IO T.Text +pAndL fn = fn2CSV (journalProfitAndLossAccountQuery) fn + +assets :: FilePath -> IO T.Text +assets fn = fn2CSV (journalAssetAccountQuery) fn + +liabilities :: FilePath -> IO T.Text +liabilities fn = fn2CSV (journalLiabilityAccountQuery) fn + +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) + +-- sign-change Income lines + +newtype YearMonth = YearMonth { unYM :: (Integer,Int) } + deriving (Eq, Show) +instance Enum YearMonth where + toEnum = YearMonth . liftA2 (,) (fromIntegral . (`div` 12)) ((1 +) . (`mod` 12)) + fromEnum = ap ((+) . (12 *) . fromIntegral . fst) (subtract 1 . snd) . unYM + +dayToYearMonth :: Day -> YearMonth +dayToYearMonth = YearMonth . (\(x,y,_) -> (x,y)) . toGregorian + +yearMonthToDay :: YearMonth -> Day +yearMonthToDay = uncurry (flip flip 1 . fromGregorian) . unYM + +jToCSV :: Bool -> Journal -> Query -> IO (T.Text) +jToCSV delta jnl q = do + let sortedtrans = sortBy (comparing tdate) (jtxns jnl) + firstTxn = tdate (head sortedtrans) + lastTxn = tdate (last sortedtrans) + firstMonth = dayToYearMonth firstTxn + lastMonth = dayToYearMonth lastTxn + q' mon = And [q, Date (dS delta mon)] + when (firstMonth == lastMonth) $ error "Need multiple months" + let reports = map (\m -> accountsReport defreportopts { no_elide_ = True } (q' m) jnl) [firstMonth..lastMonth] + reportT = accountsReport 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 + allaccounts = sort . nub . (map fst =<<) $ reports' + accounttree = accts2Tree (map (splitOn ":") allaccounts) + 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 + return $ T.concat c + +dS :: Bool -> YearMonth -> DateSpan +dS delta (YearMonth (y,m)) = DateSpan (if delta then Just startD else Nothing) (Just endD) + where + startD = fromGregorian y m 01 + endD = fromGregorian y m 31 + +fetchSeries :: [[(String, String)]] -> String -> [String] +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 ":" + |