hledger/hledger-lib/Hledger/Read/TimeclockReader.hs

123 lines
4.2 KiB
Haskell
Raw Normal View History

{-|
2016-04-13 07:10:02 +03:00
A reader for the timeclock file format generated by timeclock.el
(<http://www.emacswiki.org/emacs/TimeClock>). Example:
@
i 2007\/03\/10 12:26:00 hledger
o 2007\/03\/10 17:26:02
@
From timeclock.el 2.6:
@
2016-04-13 07:10:02 +03:00
A timeclock contains data in the form of a single entry per line.
Each entry has the form:
CODE YYYY/MM/DD HH:MM:SS [COMMENT]
CODE is one of: b, h, i, o or O. COMMENT is optional when the code is
i, o or O. The meanings of the codes are:
b Set the current time balance, or \"time debt\". Useful when
archiving old log data, when a debt must be carried forward.
The COMMENT here is the number of seconds of debt.
h Set the required working time for the given day. This must
be the first entry for that day. The COMMENT in this case is
the number of hours in this workday. Floating point amounts
are allowed.
i Clock in. The COMMENT in this case should be the name of the
project worked on.
o Clock out. COMMENT is unnecessary, but can be used to provide
a description of how the period went, for example.
O Final clock out. Whatever project was being worked on, it is
now finished. Useful for creating summary reports.
@
-}
lib: textification begins! account names The first of several conversions from String to (strict) Text, hopefully reducing space and time usage. This one shows a small improvement, with GHC 7.10.3 and text-1.2.2.1: hledger -f data/100x100x10.journal stats string: <<ghc: 39471064 bytes, 77 GCs, 198421/275048 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.001 elapsed), 0.015 MUT (0.020 elapsed), 0.010 GC (0.014 elapsed) :ghc>> text: <<ghc: 39268024 bytes, 77 GCs, 197018/270840 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.002 elapsed), 0.016 MUT (0.022 elapsed), 0.009 GC (0.011 elapsed) :ghc>> hledger -f data/1000x100x10.journal stats string: <<ghc: 318555920 bytes, 617 GCs, 2178997/7134472 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.001 elapsed), 0.129 MUT (0.136 elapsed), 0.067 GC (0.077 elapsed) :ghc>> text: <<ghc: 314248496 bytes, 612 GCs, 2074045/6617960 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.003 elapsed), 0.137 MUT (0.145 elapsed), 0.067 GC (0.079 elapsed) :ghc>> hledger -f data/10000x100x10.journal stats string: <<ghc: 3114763608 bytes, 6026 GCs, 18858950/75552024 avg/max bytes residency (11 samples), 201M in use, 0.000 INIT (0.000 elapsed), 1.331 MUT (1.372 elapsed), 0.699 GC (0.812 elapsed) :ghc>> text: <<ghc: 3071468920 bytes, 5968 GCs, 14120344/62951360 avg/max bytes residency (9 samples), 124M in use, 0.000 INIT (0.003 elapsed), 1.272 MUT (1.349 elapsed), 0.513 GC (0.578 elapsed) :ghc>> hledger -f data/100000x100x10.journal stats string: <<ghc: 31186579432 bytes, 60278 GCs, 135332581/740228992 avg/max bytes residency (13 samples), 1697M in use, 0.000 INIT (0.008 elapsed), 14.677 MUT (15.508 elapsed), 7.081 GC (8.074 elapsed) :ghc>> text: <<ghc: 30753427672 bytes, 59763 GCs, 117595958/666457240 avg/max bytes residency (14 samples), 1588M in use, 0.000 INIT (0.008 elapsed), 13.713 MUT (13.966 elapsed), 6.220 GC (7.108 elapsed) :ghc>>
2016-05-24 04:16:21 +03:00
{-# LANGUAGE OverloadedStrings #-}
2016-04-13 07:10:02 +03:00
module Hledger.Read.TimeclockReader (
-- * Reader
reader,
-- * Misc other exports
timeclockfilep,
-- * Tests
2016-04-13 07:10:02 +03:00
tests_Hledger_Read_TimeclockReader
)
where
import Prelude ()
import Prelude.Compat
import Control.Monad
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Except (ExceptT)
import Data.Maybe (fromMaybe)
lib: textification begins! account names The first of several conversions from String to (strict) Text, hopefully reducing space and time usage. This one shows a small improvement, with GHC 7.10.3 and text-1.2.2.1: hledger -f data/100x100x10.journal stats string: <<ghc: 39471064 bytes, 77 GCs, 198421/275048 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.001 elapsed), 0.015 MUT (0.020 elapsed), 0.010 GC (0.014 elapsed) :ghc>> text: <<ghc: 39268024 bytes, 77 GCs, 197018/270840 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.002 elapsed), 0.016 MUT (0.022 elapsed), 0.009 GC (0.011 elapsed) :ghc>> hledger -f data/1000x100x10.journal stats string: <<ghc: 318555920 bytes, 617 GCs, 2178997/7134472 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.001 elapsed), 0.129 MUT (0.136 elapsed), 0.067 GC (0.077 elapsed) :ghc>> text: <<ghc: 314248496 bytes, 612 GCs, 2074045/6617960 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.003 elapsed), 0.137 MUT (0.145 elapsed), 0.067 GC (0.079 elapsed) :ghc>> hledger -f data/10000x100x10.journal stats string: <<ghc: 3114763608 bytes, 6026 GCs, 18858950/75552024 avg/max bytes residency (11 samples), 201M in use, 0.000 INIT (0.000 elapsed), 1.331 MUT (1.372 elapsed), 0.699 GC (0.812 elapsed) :ghc>> text: <<ghc: 3071468920 bytes, 5968 GCs, 14120344/62951360 avg/max bytes residency (9 samples), 124M in use, 0.000 INIT (0.003 elapsed), 1.272 MUT (1.349 elapsed), 0.513 GC (0.578 elapsed) :ghc>> hledger -f data/100000x100x10.journal stats string: <<ghc: 31186579432 bytes, 60278 GCs, 135332581/740228992 avg/max bytes residency (13 samples), 1697M in use, 0.000 INIT (0.008 elapsed), 14.677 MUT (15.508 elapsed), 7.081 GC (8.074 elapsed) :ghc>> text: <<ghc: 30753427672 bytes, 59763 GCs, 117595958/666457240 avg/max bytes residency (14 samples), 1588M in use, 0.000 INIT (0.008 elapsed), 13.713 MUT (13.966 elapsed), 6.220 GC (7.108 elapsed) :ghc>>
2016-05-24 04:16:21 +03:00
-- import Data.Text (Text)
-- import qualified Data.Text as T
2011-05-28 08:11:44 +04:00
import Test.HUnit
import Text.Parsec hiding (parse)
import System.FilePath
2011-05-28 08:11:44 +04:00
import Hledger.Data
2012-05-09 19:34:05 +04:00
-- XXX too much reuse ?
import Hledger.Read.Common
2011-05-28 08:11:44 +04:00
import Hledger.Utils
reader :: Reader
reader = Reader format detect parse
format :: String
2016-04-13 07:10:02 +03:00
format = "timeclock"
2016-04-13 07:10:02 +03:00
-- | Does the given file path and data look like it might be timeclock.el's timeclock format ?
detect :: FilePath -> String -> Bool
detect f s
| f /= "-" = takeExtension f == '.':format -- from a known file name: yes if the extension is this format's name
| otherwise = regexMatches "(^|\n)[io] " s -- from stdin: yes if any line starts with "i " or "o "
2016-04-13 07:10:02 +03:00
-- | Parse and post-process a "Journal" from timeclock.el's timeclock
-- format, saving the provided file path and the current time, or give an
-- error.
parse :: Maybe FilePath -> Bool -> FilePath -> String -> ExceptT String IO Journal
2016-04-13 07:10:02 +03:00
parse _ = parseAndFinaliseJournal timeclockfilep
timeclockfilep :: ErroringJournalParser ParsedJournal
timeclockfilep = do many timeclockitemp
2016-04-13 07:10:02 +03:00
eof
j@Journal{jtxns=ts, jparsetimeclockentries=es} <- getState
-- Convert timeclock entries in this journal to transactions, closing any unfinished sessions.
-- Doing this here rather than in journalFinalise means timeclock sessions can't span file boundaries,
-- but it simplifies code above.
now <- liftIO getCurrentLocalTime
let j' = j{jtxns = ts ++ timeclockEntriesToTransactions now (reverse es), jparsetimeclockentries = []}
return j'
where
-- As all ledger line types can be distinguished by the first
-- character, excepting transactions versus empty (blank or
-- comment-only) lines, can use choice w/o try
timeclockitemp = choice [
void emptyorcommentlinep
, timeclockentryp >>= \e -> modifyState (\j -> j{jparsetimeclockentries = e : jparsetimeclockentries j})
2016-04-13 07:10:02 +03:00
] <?> "timeclock entry, or default year or historical price directive"
2016-04-13 07:10:02 +03:00
-- | Parse a timeclock entry.
timeclockentryp :: ErroringJournalParser TimeclockEntry
2016-04-13 07:10:02 +03:00
timeclockentryp = do
sourcepos <- genericSourcePos <$> getPosition
code <- oneOf "bhioO"
many1 spacenonewline
2014-02-06 07:30:01 +04:00
datetime <- datetimep
2015-09-25 03:23:52 +03:00
account <- fromMaybe "" <$> optionMaybe (many1 spacenonewline >> modifiedaccountnamep)
description <- fromMaybe "" <$> optionMaybe (many1 spacenonewline >> restofline)
2016-04-13 07:10:02 +03:00
return $ TimeclockEntry sourcepos (read [code]) datetime account description
2016-04-13 07:10:02 +03:00
tests_Hledger_Read_TimeclockReader = TestList [
]