2008-10-03 06:04:15 +04:00
|
|
|
{-|
|
|
|
|
|
2016-04-13 07:10:02 +03:00
|
|
|
A 'TimeclockEntry' is a clock-in, clock-out, or other directive in a timeclock
|
2009-04-05 03:15:42 +04:00
|
|
|
file (see timeclock.el or the command-line version). These can be
|
2009-12-16 11:07:26 +03:00
|
|
|
converted to 'Transactions' and queried like a ledger.
|
2008-10-03 06:04:15 +04:00
|
|
|
|
|
|
|
-}
|
|
|
|
|
2020-08-26 10:16:51 +03:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
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
|
|
|
|
2018-09-04 21:30:48 +03:00
|
|
|
module Hledger.Data.Timeclock (
|
|
|
|
timeclockEntriesToTransactions
|
2018-09-06 23:08:26 +03:00
|
|
|
,tests_Timeclock
|
2018-09-04 21:30:48 +03:00
|
|
|
)
|
2007-03-12 10:40:33 +03:00
|
|
|
where
|
2018-09-04 21:30:48 +03:00
|
|
|
|
2020-12-25 08:38:26 +03:00
|
|
|
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)
|
lib: textification: descriptions & codes
Slightly higher (with small files) and lower (with large files) maximum
residency, and slightly quicker for all.
hledger -f data/100x100x10.journal stats
<<ghc: 42858472 bytes, 84 GCs, 193712/269608 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.015 elapsed), 0.016 MUT (0.042 elapsed), 0.011 GC (0.119 elapsed) :ghc>>
<<ghc: 42891776 bytes, 84 GCs, 190816/260920 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.004 elapsed), 0.017 MUT (0.025 elapsed), 0.010 GC (0.015 elapsed) :ghc>>
hledger -f data/1000x1000x10.journal stats
<<ghc: 349575240 bytes, 681 GCs, 1396425/4091680 avg/max bytes residency (7 samples), 11M in use, 0.000 INIT (0.000 elapsed), 0.137 MUT (0.146 elapsed), 0.050 GC (0.057 elapsed) :ghc>>
<<ghc: 349927568 bytes, 681 GCs, 1397825/4097248 avg/max bytes residency (7 samples), 11M in use, 0.000 INIT (0.000 elapsed), 0.126 MUT (0.133 elapsed), 0.050 GC (0.057 elapsed) :ghc>>
hledger -f data/10000x1000x10.journal stats
<<ghc: 3424029496 bytes, 6658 GCs, 11403141/41077288 avg/max bytes residency (11 samples), 111M in use, 0.000 INIT (0.000 elapsed), 1.278 MUT (1.310 elapsed), 0.493 GC (0.546 elapsed) :ghc>>
<<ghc: 3427418064 bytes, 6665 GCs, 11127869/37790168 avg/max bytes residency (11 samples), 109M in use, 0.000 INIT (0.001 elapsed), 1.212 MUT (1.229 elapsed), 0.466 GC (0.519 elapsed) :ghc>>
hledger -f data/100000x1000x10.journal stats
<<ghc: 34306546248 bytes, 66727 GCs, 77030638/414617944 avg/max bytes residency (14 samples), 1012M in use, 0.000 INIT (0.000 elapsed), 12.965 MUT (13.164 elapsed), 4.771 GC (5.447 elapsed) :ghc>>
<<ghc: 34340246056 bytes, 66779 GCs, 76983178/416011480 avg/max bytes residency (14 samples), 1011M in use, 0.000 INIT (0.008 elapsed), 12.666 MUT (12.836 elapsed), 4.595 GC (5.175 elapsed) :ghc>>
2016-05-25 04:51:52 +03:00
|
|
|
import qualified Data.Text as T
|
2020-12-25 08:38:26 +03:00
|
|
|
import Data.Time.Calendar (addDays)
|
|
|
|
import Data.Time.Clock (addUTCTime, getCurrentTime)
|
|
|
|
import Data.Time.Format (defaultTimeLocale, formatTime, parseTimeM)
|
|
|
|
import Data.Time.LocalTime (LocalTime(..), TimeOfDay(..), getCurrentTimeZone,
|
|
|
|
localTimeToUTC, midnight, utc, utcToLocalTime)
|
|
|
|
import Text.Printf (printf)
|
2011-05-28 08:11:44 +04:00
|
|
|
|
2019-07-15 13:28:52 +03:00
|
|
|
import Hledger.Utils
|
2010-05-20 03:08:53 +04:00
|
|
|
import Hledger.Data.Types
|
|
|
|
import Hledger.Data.Dates
|
2012-11-20 01:20:10 +04:00
|
|
|
import Hledger.Data.Amount
|
2012-12-06 04:03:07 +04:00
|
|
|
import Hledger.Data.Posting
|
2010-05-20 03:08:53 +04:00
|
|
|
import Hledger.Data.Transaction
|
2007-03-12 10:40:33 +03:00
|
|
|
|
2016-04-13 07:10:02 +03:00
|
|
|
instance Show TimeclockEntry where
|
2015-04-28 23:54:36 +03:00
|
|
|
show t = printf "%s %s %s %s" (show $ tlcode t) (show $ tldatetime t) (tlaccount t) (tldescription t)
|
2007-03-12 10:40:33 +03:00
|
|
|
|
2016-04-13 07:10:02 +03:00
|
|
|
instance Show TimeclockCode where
|
2009-04-04 00:04:51 +04:00
|
|
|
show SetBalance = "b"
|
|
|
|
show SetRequiredHours = "h"
|
|
|
|
show In = "i"
|
|
|
|
show Out = "o"
|
|
|
|
show FinalOut = "O"
|
|
|
|
|
2016-04-13 07:10:02 +03:00
|
|
|
instance Read TimeclockCode where
|
2009-04-04 00:04:51 +04:00
|
|
|
readsPrec _ ('b' : xs) = [(SetBalance, xs)]
|
|
|
|
readsPrec _ ('h' : xs) = [(SetRequiredHours, xs)]
|
|
|
|
readsPrec _ ('i' : xs) = [(In, xs)]
|
|
|
|
readsPrec _ ('o' : xs) = [(Out, xs)]
|
|
|
|
readsPrec _ ('O' : xs) = [(FinalOut, xs)]
|
|
|
|
readsPrec _ _ = []
|
|
|
|
|
2010-07-13 10:30:06 +04:00
|
|
|
-- | Convert time log entries to journal transactions. When there is no
|
2009-01-26 23:22:42 +03:00
|
|
|
-- clockout, add one with the provided current time. Sessions crossing
|
2009-03-15 15:42:03 +03:00
|
|
|
-- midnight are split into days to give accurate per-day totals.
|
2016-04-13 07:10:02 +03:00
|
|
|
timeclockEntriesToTransactions :: LocalTime -> [TimeclockEntry] -> [Transaction]
|
|
|
|
timeclockEntriesToTransactions _ [] = []
|
|
|
|
timeclockEntriesToTransactions now [i]
|
2020-01-12 13:26:30 +03:00
|
|
|
| tlcode i /= In = errorExpectedCodeButGot In i
|
2016-04-13 07:10:02 +03:00
|
|
|
| odate > idate = entryFromTimeclockInOut i o' : timeclockEntriesToTransactions now [i',o]
|
|
|
|
| otherwise = [entryFromTimeclockInOut i o]
|
2009-03-15 15:42:03 +03:00
|
|
|
where
|
2016-04-13 07:10:02 +03:00
|
|
|
o = TimeclockEntry (tlsourcepos i) Out end "" ""
|
2009-04-01 09:00:08 +04:00
|
|
|
end = if itime > now then itime else now
|
2009-03-15 15:42:03 +03:00
|
|
|
(itime,otime) = (tldatetime i,tldatetime o)
|
|
|
|
(idate,odate) = (localDay itime,localDay otime)
|
|
|
|
o' = o{tldatetime=itime{localDay=idate, localTimeOfDay=TimeOfDay 23 59 59}}
|
|
|
|
i' = i{tldatetime=itime{localDay=addDays 1 idate, localTimeOfDay=midnight}}
|
2016-04-13 07:10:02 +03:00
|
|
|
timeclockEntriesToTransactions now (i:o:rest)
|
2020-01-12 13:26:30 +03:00
|
|
|
| tlcode i /= In = errorExpectedCodeButGot In i
|
|
|
|
| tlcode o /= Out =errorExpectedCodeButGot Out o
|
2016-04-13 07:10:02 +03:00
|
|
|
| odate > idate = entryFromTimeclockInOut i o' : timeclockEntriesToTransactions now (i':o:rest)
|
|
|
|
| otherwise = entryFromTimeclockInOut i o : timeclockEntriesToTransactions now rest
|
2009-01-26 23:22:42 +03:00
|
|
|
where
|
|
|
|
(itime,otime) = (tldatetime i,tldatetime o)
|
|
|
|
(idate,odate) = (localDay itime,localDay otime)
|
|
|
|
o' = o{tldatetime=itime{localDay=idate, localTimeOfDay=TimeOfDay 23 59 59}}
|
|
|
|
i' = i{tldatetime=itime{localDay=addDays 1 idate, localTimeOfDay=midnight}}
|
2019-02-14 16:14:52 +03:00
|
|
|
{- HLINT ignore timeclockEntriesToTransactions -}
|
2007-03-12 10:40:33 +03:00
|
|
|
|
2020-01-12 13:26:30 +03:00
|
|
|
errorExpectedCodeButGot expected actual = errorWithSourceLine line $ "expected timeclock code " ++ (show expected) ++ " but got " ++ show (tlcode actual)
|
|
|
|
where
|
|
|
|
line = case tlsourcepos actual of
|
|
|
|
GenericSourcePos _ l _ -> l
|
|
|
|
JournalSourcePos _ (l, _) -> l
|
|
|
|
|
|
|
|
errorWithSourceLine line msg = error $ "line " ++ show line ++ ": " ++ msg
|
|
|
|
|
2016-04-13 07:10:02 +03:00
|
|
|
-- | Convert a timeclock clockin and clockout entry to an equivalent journal
|
2010-07-13 10:30:06 +04:00
|
|
|
-- transaction, representing the time expenditure. Note this entry is not balanced,
|
2008-10-15 23:11:06 +04:00
|
|
|
-- since we omit the \"assets:time\" transaction for simpler output.
|
2016-04-13 07:10:02 +03:00
|
|
|
entryFromTimeclockInOut :: TimeclockEntry -> TimeclockEntry -> Transaction
|
|
|
|
entryFromTimeclockInOut i o
|
2009-04-03 14:58:05 +04:00
|
|
|
| otime >= itime = t
|
2020-10-28 04:53:37 +03:00
|
|
|
| otherwise = error' . T.unpack $
|
|
|
|
"clock-out time less than clock-in time in:\n" <> showTransaction t -- PARTIAL:
|
2007-03-12 10:40:33 +03:00
|
|
|
where
|
2009-12-16 11:07:26 +03:00
|
|
|
t = Transaction {
|
2015-10-30 06:12:46 +03:00
|
|
|
tindex = 0,
|
2014-08-01 04:32:42 +04:00
|
|
|
tsourcepos = tlsourcepos i,
|
|
|
|
tdate = idate,
|
|
|
|
tdate2 = Nothing,
|
2015-05-16 21:51:35 +03:00
|
|
|
tstatus = Cleared,
|
2014-08-01 04:32:42 +04:00
|
|
|
tcode = "",
|
2015-04-28 23:54:36 +03:00
|
|
|
tdescription = desc,
|
2014-08-01 04:32:42 +04:00
|
|
|
tcomment = "",
|
|
|
|
ttags = [],
|
|
|
|
tpostings = ps,
|
2019-01-04 23:01:45 +03:00
|
|
|
tprecedingcomment=""
|
2008-12-11 04:35:07 +03:00
|
|
|
}
|
2009-01-25 10:06:59 +03:00
|
|
|
itime = tldatetime i
|
|
|
|
otime = tldatetime o
|
|
|
|
itod = localTimeOfDay itime
|
|
|
|
otod = localTimeOfDay otime
|
|
|
|
idate = localDay itime
|
lib: textification: descriptions & codes
Slightly higher (with small files) and lower (with large files) maximum
residency, and slightly quicker for all.
hledger -f data/100x100x10.journal stats
<<ghc: 42858472 bytes, 84 GCs, 193712/269608 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.015 elapsed), 0.016 MUT (0.042 elapsed), 0.011 GC (0.119 elapsed) :ghc>>
<<ghc: 42891776 bytes, 84 GCs, 190816/260920 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.004 elapsed), 0.017 MUT (0.025 elapsed), 0.010 GC (0.015 elapsed) :ghc>>
hledger -f data/1000x1000x10.journal stats
<<ghc: 349575240 bytes, 681 GCs, 1396425/4091680 avg/max bytes residency (7 samples), 11M in use, 0.000 INIT (0.000 elapsed), 0.137 MUT (0.146 elapsed), 0.050 GC (0.057 elapsed) :ghc>>
<<ghc: 349927568 bytes, 681 GCs, 1397825/4097248 avg/max bytes residency (7 samples), 11M in use, 0.000 INIT (0.000 elapsed), 0.126 MUT (0.133 elapsed), 0.050 GC (0.057 elapsed) :ghc>>
hledger -f data/10000x1000x10.journal stats
<<ghc: 3424029496 bytes, 6658 GCs, 11403141/41077288 avg/max bytes residency (11 samples), 111M in use, 0.000 INIT (0.000 elapsed), 1.278 MUT (1.310 elapsed), 0.493 GC (0.546 elapsed) :ghc>>
<<ghc: 3427418064 bytes, 6665 GCs, 11127869/37790168 avg/max bytes residency (11 samples), 109M in use, 0.000 INIT (0.001 elapsed), 1.212 MUT (1.229 elapsed), 0.466 GC (0.519 elapsed) :ghc>>
hledger -f data/100000x1000x10.journal stats
<<ghc: 34306546248 bytes, 66727 GCs, 77030638/414617944 avg/max bytes residency (14 samples), 1012M in use, 0.000 INIT (0.000 elapsed), 12.965 MUT (13.164 elapsed), 4.771 GC (5.447 elapsed) :ghc>>
<<ghc: 34340246056 bytes, 66779 GCs, 76983178/416011480 avg/max bytes residency (14 samples), 1011M in use, 0.000 INIT (0.008 elapsed), 12.666 MUT (12.836 elapsed), 4.595 GC (5.175 elapsed) :ghc>>
2016-05-25 04:51:52 +03:00
|
|
|
desc | T.null (tldescription i) = T.pack $ showtime itod ++ "-" ++ showtime otod
|
|
|
|
| otherwise = tldescription i
|
2015-04-28 23:54:36 +03:00
|
|
|
showtime = take 5 . show
|
2012-11-20 01:20:10 +04:00
|
|
|
hours = elapsedSeconds (toutc otime) (toutc itime) / 3600 where toutc = localTimeToUTC utc
|
2015-04-28 23:54:36 +03:00
|
|
|
acctname = tlaccount i
|
2012-11-20 01:20:10 +04:00
|
|
|
amount = Mixed [hrs hours]
|
2012-12-06 04:03:07 +04:00
|
|
|
ps = [posting{paccount=acctname, pamount=amount, ptype=VirtualPosting, ptransaction=Just t}]
|
|
|
|
|
2010-05-22 23:00:20 +04:00
|
|
|
|
2018-09-04 21:30:48 +03:00
|
|
|
-- tests
|
|
|
|
|
2018-09-06 23:08:26 +03:00
|
|
|
tests_Timeclock = tests "Timeclock" [
|
2019-11-27 00:56:14 +03:00
|
|
|
testCaseSteps "timeclockEntriesToTransactions tests" $ \step -> do
|
|
|
|
step "gathering data"
|
|
|
|
today <- getCurrentDay
|
|
|
|
now' <- getCurrentTime
|
|
|
|
tz <- getCurrentTimeZone
|
|
|
|
let now = utcToLocalTime tz now'
|
|
|
|
nowstr = showtime now
|
|
|
|
yesterday = prevday today
|
|
|
|
clockin = TimeclockEntry nullsourcepos In
|
|
|
|
mktime d = LocalTime d . fromMaybe midnight .
|
|
|
|
parseTimeM True defaultTimeLocale "%H:%M:%S"
|
|
|
|
showtime = formatTime defaultTimeLocale "%H:%M"
|
|
|
|
txndescs = map (T.unpack . tdescription) . timeclockEntriesToTransactions now
|
|
|
|
future = utcToLocalTime tz $ addUTCTime 100 now'
|
|
|
|
futurestr = showtime future
|
|
|
|
step "started yesterday, split session at midnight"
|
|
|
|
txndescs [clockin (mktime yesterday "23:00:00") "" ""] @?= ["23:00-23:59","00:00-"++nowstr]
|
|
|
|
step "split multi-day sessions at each midnight"
|
|
|
|
txndescs [clockin (mktime (addDays (-2) today) "23:00:00") "" ""] @?= ["23:00-23:59","00:00-23:59","00:00-"++nowstr]
|
|
|
|
step "auto-clock-out if needed"
|
|
|
|
txndescs [clockin (mktime today "00:00:00") "" ""] @?= ["00:00-"++nowstr]
|
|
|
|
step "use the clockin time for auto-clockout if it's in the future"
|
|
|
|
txndescs [clockin future "" ""] @?= [printf "%s-%s" futurestr futurestr]
|
2014-08-01 04:32:42 +04:00
|
|
|
]
|