2010-05-30 23:11:58 +04:00
|
|
|
{-|
|
|
|
|
|
2016-04-13 07:10:02 +03:00
|
|
|
A reader for the timeclock file format generated by timeclock.el
|
2012-03-24 22:08:11 +04:00
|
|
|
(<http://www.emacswiki.org/emacs/TimeClock>). Example:
|
|
|
|
|
|
|
|
@
|
|
|
|
i 2007\/03\/10 12:26:00 hledger
|
|
|
|
o 2007\/03\/10 17:26:02
|
|
|
|
@
|
2010-05-30 23:11:58 +04:00
|
|
|
|
|
|
|
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.
|
2010-05-30 23:11:58 +04:00
|
|
|
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.
|
|
|
|
@
|
|
|
|
|
|
|
|
-}
|
|
|
|
|
2018-06-04 22:30:43 +03:00
|
|
|
{-# LANGUAGE OverloadedStrings, PackageImports #-}
|
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
|
|
|
|
2016-04-13 07:10:02 +03:00
|
|
|
module Hledger.Read.TimeclockReader (
|
2012-03-24 22:08:11 +04:00
|
|
|
-- * Reader
|
|
|
|
reader,
|
2016-05-18 05:46:54 +03:00
|
|
|
-- * Misc other exports
|
|
|
|
timeclockfilep,
|
2010-05-31 05:15:18 +04:00
|
|
|
)
|
2010-05-30 23:11:58 +04:00
|
|
|
where
|
2016-07-29 18:57:10 +03:00
|
|
|
import Prelude ()
|
2018-06-05 02:28:28 +03:00
|
|
|
import "base-compat-batteries" Prelude.Compat
|
2016-07-29 18:57:10 +03:00
|
|
|
import Control.Monad
|
|
|
|
import Control.Monad.Except (ExceptT)
|
|
|
|
import Control.Monad.State.Strict
|
|
|
|
import Data.Maybe (fromMaybe)
|
|
|
|
import Data.Text (Text)
|
lib: textification: parse stream
10% more allocation, but 35% lower maximum residency, and slightly quicker.
hledger -f data/100x100x10.journal stats
<<ghc: 39327768 bytes, 77 GCs, 196834/269496 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.010 elapsed), 0.020 MUT (0.092 elapsed), 0.014 GC (0.119 elapsed) :ghc>>
<<ghc: 42842136 bytes, 84 GCs, 194010/270912 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.009 elapsed), 0.016 MUT (0.029 elapsed), 0.012 GC (0.120 elapsed) :ghc>>
hledger -f data/1000x1000x10.journal stats
<<ghc: 314291440 bytes, 612 GCs, 2070776/6628048 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.000 elapsed), 0.128 MUT (0.144 elapsed), 0.059 GC (0.070 elapsed) :ghc>>
<<ghc: 349558872 bytes, 681 GCs, 1397597/4106384 avg/max bytes residency (7 samples), 11M in use, 0.000 INIT (0.004 elapsed), 0.124 MUT (0.133 elapsed), 0.047 GC (0.053 elapsed) :ghc>>
hledger -f data/10000x1000x10.journal stats
<<ghc: 3070026824 bytes, 5973 GCs, 12698030/62951784 avg/max bytes residency (10 samples), 124M in use, 0.000 INIT (0.002 elapsed), 1.268 MUT (1.354 elapsed), 0.514 GC (0.587 elapsed) :ghc>>
<<ghc: 3424013128 bytes, 6658 GCs, 11405501/41071624 avg/max bytes residency (11 samples), 111M in use, 0.000 INIT (0.001 elapsed), 1.343 MUT (1.406 elapsed), 0.511 GC (0.573 elapsed) :ghc>>
hledger -f data/100000x1000x10.journal stats
<<ghc: 30753387392 bytes, 59811 GCs, 117615462/666703600 avg/max bytes residency (14 samples), 1588M in use, 0.000 INIT (0.000 elapsed), 12.068 MUT (12.238 elapsed), 6.015 GC (7.190 elapsed) :ghc>>
<<ghc: 34306530696 bytes, 66727 GCs, 76806196/414629312 avg/max bytes residency (14 samples), 1009M in use, 0.000 INIT (0.010 elapsed), 14.357 MUT (16.370 elapsed), 5.298 GC (6.534 elapsed) :ghc>>
2016-05-25 01:58:23 +03:00
|
|
|
import qualified Data.Text as T
|
2018-05-22 01:47:56 +03:00
|
|
|
import Text.Megaparsec hiding (parse)
|
2011-05-28 08:11:44 +04:00
|
|
|
|
2016-07-29 18:57:10 +03:00
|
|
|
import Hledger.Data
|
2012-05-09 19:34:05 +04:00
|
|
|
-- XXX too much reuse ?
|
2016-07-29 18:57:10 +03:00
|
|
|
import Hledger.Read.Common
|
|
|
|
import Hledger.Utils
|
2010-05-30 23:11:58 +04:00
|
|
|
|
|
|
|
|
2010-06-25 18:56:48 +04:00
|
|
|
reader :: Reader
|
2016-11-19 00:24:57 +03:00
|
|
|
reader = Reader
|
|
|
|
{rFormat = "timeclock"
|
|
|
|
,rExtensions = ["timeclock"]
|
|
|
|
,rParser = parse
|
2016-11-20 21:42:12 +03:00
|
|
|
,rExperimental = False
|
2016-11-19 00:24:57 +03:00
|
|
|
}
|
2010-06-25 18:56:48 +04:00
|
|
|
|
2016-04-13 07:10:02 +03:00
|
|
|
-- | Parse and post-process a "Journal" from timeclock.el's timeclock
|
2010-05-30 23:11:58 +04:00
|
|
|
-- format, saving the provided file path and the current time, or give an
|
|
|
|
-- error.
|
2018-04-17 00:47:04 +03:00
|
|
|
parse :: InputOpts -> FilePath -> Text -> ExceptT String IO Journal
|
2018-09-26 01:07:58 +03:00
|
|
|
parse = parseAndFinaliseJournal' timeclockfilep
|
2010-05-30 23:11:58 +04:00
|
|
|
|
2018-06-06 09:29:52 +03:00
|
|
|
timeclockfilep :: MonadIO m => JournalParser m ParsedJournal
|
2016-05-23 10:32:55 +03:00
|
|
|
timeclockfilep = do many timeclockitemp
|
2016-04-13 07:10:02 +03:00
|
|
|
eof
|
2016-08-15 00:50:03 +03:00
|
|
|
j@Journal{jparsetimeclockentries=es} <- get
|
2016-05-23 10:32:55 +03:00
|
|
|
-- 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
|
2016-08-15 00:50:03 +03:00
|
|
|
-- entries have been parsed in reverse order. timeclockEntriesToTransactions
|
|
|
|
-- expects them to be in normal order, then we must reverse again since
|
|
|
|
-- journalFinalise expects them in reverse order
|
|
|
|
let j' = j{jtxns = reverse $ timeclockEntriesToTransactions now $ reverse es, jparsetimeclockentries = []}
|
2016-05-23 10:32:55 +03:00
|
|
|
return j'
|
2014-09-11 00:07:53 +04:00
|
|
|
where
|
2010-05-30 23:11:58 +04:00
|
|
|
-- 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
|
2019-07-15 13:28:52 +03:00
|
|
|
timeclockitemp = choice [
|
2018-05-16 03:59:49 +03:00
|
|
|
void (lift emptyorcommentlinep)
|
2016-07-29 18:57:10 +03:00
|
|
|
, timeclockentryp >>= \e -> modify' (\j -> j{jparsetimeclockentries = e : jparsetimeclockentries j})
|
2020-01-12 13:26:30 +03:00
|
|
|
] <?> "timeclock entry, comment line, or empty line"
|
2010-05-30 23:11:58 +04:00
|
|
|
|
2016-04-13 07:10:02 +03:00
|
|
|
-- | Parse a timeclock entry.
|
2017-07-27 14:59:55 +03:00
|
|
|
timeclockentryp :: JournalParser m TimeclockEntry
|
2016-04-13 07:10:02 +03:00
|
|
|
timeclockentryp = do
|
2018-09-30 04:32:08 +03:00
|
|
|
sourcepos <- genericSourcePos <$> lift getSourcePos
|
2016-07-29 18:57:10 +03:00
|
|
|
code <- oneOf ("bhioO" :: [Char])
|
2018-03-25 16:53:44 +03:00
|
|
|
lift (skipSome spacenonewline)
|
2014-02-06 07:30:01 +04:00
|
|
|
datetime <- datetimep
|
2018-03-25 16:53:44 +03:00
|
|
|
account <- fromMaybe "" <$> optional (lift (skipSome spacenonewline) >> modifiedaccountnamep)
|
|
|
|
description <- T.pack . fromMaybe "" <$> lift (optional (skipSome spacenonewline >> restofline))
|
2016-04-13 07:10:02 +03:00
|
|
|
return $ TimeclockEntry sourcepos (read [code]) datetime account description
|
2010-05-30 23:11:58 +04:00
|
|
|
|
|
|
|
|