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>>
		
			
				
	
	
		
			123 lines
		
	
	
		
			4.2 KiB
		
	
	
	
		
			Haskell
		
	
	
	
	
	
			
		
		
	
	
			123 lines
		
	
	
		
			4.2 KiB
		
	
	
	
		
			Haskell
		
	
	
	
	
	
| {-|
 | |
| 
 | |
| 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:
 | |
| 
 | |
| @
 | |
| 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.
 | |
| @
 | |
| 
 | |
| -}
 | |
| 
 | |
| {-# LANGUAGE OverloadedStrings #-}
 | |
| 
 | |
| module Hledger.Read.TimeclockReader (
 | |
|   -- * Reader
 | |
|   reader,
 | |
|   -- * Misc other exports
 | |
|   timeclockfilep,
 | |
|   -- * Tests
 | |
|   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)
 | |
| import Data.Text (Text)
 | |
| import qualified Data.Text as T
 | |
| import Test.HUnit
 | |
| import Text.Parsec hiding (parse)
 | |
| import System.FilePath
 | |
| 
 | |
| import Hledger.Data
 | |
| -- XXX too much reuse ?
 | |
| import Hledger.Read.Common
 | |
| import Hledger.Utils
 | |
| 
 | |
| 
 | |
| reader :: Reader
 | |
| reader = Reader format detect parse
 | |
| 
 | |
| format :: String
 | |
| format = "timeclock"
 | |
| 
 | |
| -- | Does the given file path and data look like it might be timeclock.el's timeclock format ?
 | |
| detect :: FilePath -> Text -> Bool
 | |
| detect f t
 | |
|   | f /= "-"  = takeExtension f == '.':format -- from a known file name: yes if the extension is this format's name
 | |
|   | otherwise = regexMatches "(^|\n)[io] " $ T.unpack t  -- from stdin: yes if any line starts with "i " or "o "
 | |
| 
 | |
| -- | 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 -> Text -> ExceptT String IO Journal
 | |
| parse _ = parseAndFinaliseJournal timeclockfilep
 | |
| 
 | |
| timeclockfilep :: ErroringJournalParser ParsedJournal
 | |
| timeclockfilep = do many timeclockitemp
 | |
|                     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})
 | |
|                           ] <?> "timeclock entry, or default year or historical price directive"
 | |
| 
 | |
| -- | Parse a timeclock entry.
 | |
| timeclockentryp :: ErroringJournalParser TimeclockEntry
 | |
| timeclockentryp = do
 | |
|   sourcepos <- genericSourcePos <$> getPosition
 | |
|   code <- oneOf "bhioO"
 | |
|   many1 spacenonewline
 | |
|   datetime <- datetimep
 | |
|   account <- fromMaybe "" <$> optionMaybe (many1 spacenonewline >> modifiedaccountnamep)
 | |
|   description <- T.pack . fromMaybe "" <$> optionMaybe (many1 spacenonewline >> restofline)
 | |
|   return $ TimeclockEntry sourcepos (read [code]) datetime account description
 | |
| 
 | |
| tests_Hledger_Read_TimeclockReader = TestList [
 | |
|  ]
 | |
| 
 |