lib: timedot format, convenient for time logging
Timedot is a plain text format for logging dated, categorised quantities (eg time), supported by hledger. It is convenient for approximate and retroactive time logging, eg when the real-time clock-in/out required with a timeclock file is too precise or too interruptive. It can be formatted like a bar chart, making clear at a glance where time was spent.
This commit is contained in:
		
							parent
							
								
									36970f7b19
								
							
						
					
					
						commit
						06b54bf05e
					
				
							
								
								
									
										1
									
								
								Makefile
									
									
									
									
									
								
							
							
						
						
									
										1
									
								
								Makefile
									
									
									
									
									
								
							| @ -1045,6 +1045,7 @@ MANPAGES=\ | |||||||
| 	hledger-lib/hledger_csv.5 \
 | 	hledger-lib/hledger_csv.5 \
 | ||||||
| 	hledger-lib/hledger_journal.5 \
 | 	hledger-lib/hledger_journal.5 \
 | ||||||
| 	hledger-lib/hledger_timelog.5 \
 | 	hledger-lib/hledger_timelog.5 \
 | ||||||
|  | 	hledger-lib/hledger_timedot.5 \
 | ||||||
| 	hledger/hledger.1 \
 | 	hledger/hledger.1 \
 | ||||||
| 	hledger-ui/hledger-ui.1 \
 | 	hledger-ui/hledger-ui.1 \
 | ||||||
| 	hledger-web/hledger-web.1 \
 | 	hledger-web/hledger-web.1 \
 | ||||||
|  | |||||||
							
								
								
									
										22
									
								
								data/sample.timedot
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										22
									
								
								data/sample.timedot
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,22 @@ | |||||||
|  | 2/1 | ||||||
|  | fos.haskell  .... | ||||||
|  | biz.research  . | ||||||
|  | inc.client1  .... .... .... .... .... .... | ||||||
|  | 
 | ||||||
|  | 2/2 | ||||||
|  | biz.research  . | ||||||
|  | inc.client1  .... .... .. | ||||||
|  | 
 | ||||||
|  | 2/3 | ||||||
|  | biz.research  . | ||||||
|  | fos.hledger  .... .... ... | ||||||
|  | biz.it  .... .. | ||||||
|  | inc.client1  .... .... .... .... .... | ||||||
|  | 
 | ||||||
|  | 2/4 | ||||||
|  | biz.research  .... .. | ||||||
|  | fos.hledger  .... .... .... | ||||||
|  | fos.ledger  . | ||||||
|  | fos.haskell  .. | ||||||
|  | inc.client1  .... .... | ||||||
|  | 
 | ||||||
| @ -48,6 +48,7 @@ import Hledger.Data.Dates (getCurrentDay) | |||||||
| import Hledger.Data.Types | import Hledger.Data.Types | ||||||
| import Hledger.Data.Journal (nullctx) | import Hledger.Data.Journal (nullctx) | ||||||
| import Hledger.Read.JournalReader as JournalReader | import Hledger.Read.JournalReader as JournalReader | ||||||
|  | import Hledger.Read.TimedotReader as TimedotReader | ||||||
| import Hledger.Read.TimelogReader as TimelogReader | import Hledger.Read.TimelogReader as TimelogReader | ||||||
| import Hledger.Read.CsvReader as CsvReader | import Hledger.Read.CsvReader as CsvReader | ||||||
| import Hledger.Utils | import Hledger.Utils | ||||||
| @ -65,6 +66,7 @@ readers :: [Reader] | |||||||
| readers = [ | readers = [ | ||||||
|   JournalReader.reader |   JournalReader.reader | ||||||
|  ,TimelogReader.reader |  ,TimelogReader.reader | ||||||
|  |  ,TimedotReader.reader | ||||||
|  ,CsvReader.reader |  ,CsvReader.reader | ||||||
|  ] |  ] | ||||||
| 
 | 
 | ||||||
|  | |||||||
| @ -29,6 +29,7 @@ module Hledger.Read.JournalReader ( | |||||||
|   defaultyeardirectivep, |   defaultyeardirectivep, | ||||||
|   marketpricedirectivep, |   marketpricedirectivep, | ||||||
|   datetimep, |   datetimep, | ||||||
|  |   datep, | ||||||
|   codep, |   codep, | ||||||
|   accountnamep, |   accountnamep, | ||||||
|   modifiedaccountnamep, |   modifiedaccountnamep, | ||||||
|  | |||||||
							
								
								
									
										156
									
								
								hledger-lib/Hledger/Read/TimedotReader.hs
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										156
									
								
								hledger-lib/Hledger/Read/TimedotReader.hs
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,156 @@ | |||||||
|  | {-| | ||||||
|  | 
 | ||||||
|  | A reader for the new "timedot" file format (tentative name). | ||||||
|  | Example: | ||||||
|  | 
 | ||||||
|  | @ | ||||||
|  | #DATE | ||||||
|  | #ACCT DOTS  # Each dot represents 15m, spaces are ignored | ||||||
|  | 
 | ||||||
|  | # on 2/1, 1h was spent on FOSS haskell work, 0.25h on research, etc. | ||||||
|  | 2/1 | ||||||
|  | fos.haskell  .... .. | ||||||
|  | biz.research . | ||||||
|  | inc.client1  .... .... .... .... .... .... | ||||||
|  | 
 | ||||||
|  | 2/2 | ||||||
|  | biz.research . | ||||||
|  | inc.client1 .... .... .. | ||||||
|  | 
 | ||||||
|  | @ | ||||||
|  | 
 | ||||||
|  | -} | ||||||
|  | 
 | ||||||
|  | module Hledger.Read.TimedotReader ( | ||||||
|  |   -- * Reader | ||||||
|  |   reader, | ||||||
|  |   -- * Tests | ||||||
|  |   tests_Hledger_Read_TimedotReader | ||||||
|  | ) | ||||||
|  | where | ||||||
|  | import Prelude () | ||||||
|  | import Prelude.Compat | ||||||
|  | import Control.Monad (liftM) | ||||||
|  | import Control.Monad.Except (ExceptT) | ||||||
|  | import Data.Char (isSpace) | ||||||
|  | import Data.List (foldl') | ||||||
|  | import Data.Maybe | ||||||
|  | import Test.HUnit | ||||||
|  | import Text.Parsec hiding (parse) | ||||||
|  | import System.FilePath | ||||||
|  | 
 | ||||||
|  | import Hledger.Data | ||||||
|  | -- XXX too much reuse ? | ||||||
|  | import Hledger.Read.JournalReader ( | ||||||
|  |   datep, numberp, defaultyeardirectivep, emptyorcommentlinep, followingcommentp, | ||||||
|  |   parseAndFinaliseJournal, modifiedaccountnamep, genericSourcePos | ||||||
|  |   ) | ||||||
|  | import Hledger.Utils hiding (ptrace) | ||||||
|  | 
 | ||||||
|  | -- easier to toggle this here sometimes | ||||||
|  | -- import qualified Hledger.Utils (ptrace) | ||||||
|  | -- ptrace = Hledger.Utils.ptrace | ||||||
|  | ptrace = return | ||||||
|  | 
 | ||||||
|  | reader :: Reader | ||||||
|  | reader = Reader format detect parse | ||||||
|  | 
 | ||||||
|  | format :: String | ||||||
|  | format = "timedot" | ||||||
|  | 
 | ||||||
|  | -- | Does the given file path and data look like it contain this format ? | ||||||
|  | detect :: FilePath -> String -> Bool | ||||||
|  | detect f _s | ||||||
|  |   | f /= "-"  = takeExtension f == '.':format  -- from a file: yes if the extension matches the format name | ||||||
|  |   | otherwise = False                          -- from stdin: yes if... | ||||||
|  | 
 | ||||||
|  | -- | Parse and post-process a "Journal" from the timedot format, or give an error. | ||||||
|  | parse :: Maybe FilePath -> Bool -> FilePath -> String -> ExceptT String IO Journal | ||||||
|  | parse _ = parseAndFinaliseJournal timedotfilep | ||||||
|  | 
 | ||||||
|  | timedotfilep :: ParsecT [Char] JournalContext (ExceptT String IO) (JournalUpdate, JournalContext) | ||||||
|  | timedotfilep = do items <- many timedotfileitemp | ||||||
|  |                   eof | ||||||
|  |                   ctx <- getState | ||||||
|  |                   return (liftM (foldl' (\acc new x -> new (acc x)) id) $ sequence items, ctx) | ||||||
|  |     where | ||||||
|  |       timedotfileitemp = do | ||||||
|  |         ptrace "timedotfileitemp" | ||||||
|  |         choice [ | ||||||
|  |          defaultyeardirectivep, | ||||||
|  |          emptyorcommentlinep >> return (return id), | ||||||
|  |          liftM (return . addTransactions) timedotdayp | ||||||
|  |          ] <?> "timedot day entry, or default year or comment line or blank line" | ||||||
|  | 
 | ||||||
|  | addTransactions :: [Transaction] -> Journal -> Journal | ||||||
|  | addTransactions ts j = foldr ($) j (map addTransaction ts) -- XXX | ||||||
|  | 
 | ||||||
|  | -- | Parse timedot day entries to zero or more time transactions for that day. | ||||||
|  | -- @ | ||||||
|  | -- 2/1 | ||||||
|  | -- fos.haskell  .... .. | ||||||
|  | -- biz.research . | ||||||
|  | -- inc.client1  .... .... .... .... .... .... | ||||||
|  | -- @ | ||||||
|  | timedotdayp :: ParsecT [Char] JournalContext (ExceptT String IO) [Transaction] | ||||||
|  | timedotdayp = do | ||||||
|  |   ptrace " timedotdayp" | ||||||
|  |   d <- datep <* eolof | ||||||
|  |   es <- catMaybes <$> many (const Nothing <$> emptyorcommentlinep <|> | ||||||
|  |                             Just <$> (notFollowedBy datep >> timedotentryp)) | ||||||
|  |   return $ map (\t -> t{tdate=d}) es -- <$> many timedotentryp | ||||||
|  | 
 | ||||||
|  | -- | Parse a single timedot entry to one (dateless) transaction. | ||||||
|  | -- @ | ||||||
|  | -- fos.haskell  .... .. | ||||||
|  | -- @ | ||||||
|  | timedotentryp :: ParsecT [Char] JournalContext (ExceptT String IO) Transaction | ||||||
|  | timedotentryp = do | ||||||
|  |   ptrace "  timedotentryp" | ||||||
|  |   pos <- genericSourcePos <$> getPosition | ||||||
|  |   a <- modifiedaccountnamep | ||||||
|  |   many spacenonewline | ||||||
|  |   hours <- | ||||||
|  |     try (followingcommentp >> return 0) | ||||||
|  |     <|> (timedotdurationp <* | ||||||
|  |          (try followingcommentp <|> (newline >> return ""))) | ||||||
|  |   let t = nulltransaction{ | ||||||
|  |         tsourcepos = pos, | ||||||
|  |         tstatus    = Cleared, | ||||||
|  |         tpostings  = [ | ||||||
|  |           nullposting{paccount=a | ||||||
|  |                      ,pamount=Mixed [setAmountPrecision 2 $ num hours]  -- don't assume hours; do set precision to 2 | ||||||
|  |                      ,ptype=VirtualPosting | ||||||
|  |                      ,ptransaction=Just t | ||||||
|  |                      } | ||||||
|  |           ] | ||||||
|  |         } | ||||||
|  |   return t | ||||||
|  | 
 | ||||||
|  | timedotdurationp :: ParsecT [Char] JournalContext (ExceptT String IO) Quantity | ||||||
|  | timedotdurationp = try timedotnumberp <|> timedotdotsp | ||||||
|  | 
 | ||||||
|  | -- | Parse a duration written as a decimal number of hours (optionally followed by the letter h). | ||||||
|  | -- @ | ||||||
|  | -- 1.5h | ||||||
|  | -- @ | ||||||
|  | timedotnumberp :: ParsecT [Char] JournalContext (ExceptT String IO) Quantity | ||||||
|  | timedotnumberp = do | ||||||
|  |    (q, _, _, _) <- numberp | ||||||
|  |    many spacenonewline | ||||||
|  |    optional $ char 'h' | ||||||
|  |    many spacenonewline | ||||||
|  |    return q | ||||||
|  | 
 | ||||||
|  | -- | Parse a quantity written as a line of dots, each representing 0.25. | ||||||
|  | -- @ | ||||||
|  | -- .... .. | ||||||
|  | -- @ | ||||||
|  | timedotdotsp :: ParsecT [Char] JournalContext (ExceptT String IO) Quantity | ||||||
|  | timedotdotsp = do | ||||||
|  |   dots <- filter (not.isSpace) <$> many (oneOf ". ") | ||||||
|  |   return $ (/4) $ fromIntegral $ length dots | ||||||
|  | 
 | ||||||
|  | tests_Hledger_Read_TimedotReader = TestList [ | ||||||
|  |  ] | ||||||
|  | 
 | ||||||
							
								
								
									
										206
									
								
								hledger-lib/Hledger/Read/Util.hs
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										206
									
								
								hledger-lib/Hledger/Read/Util.hs
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,206 @@ | |||||||
|  | {-# LANGUAGE ScopedTypeVariables #-} | ||||||
|  | module Hledger.Read.Util | ||||||
|  | where | ||||||
|  | import Control.Monad.Except | ||||||
|  | import Data.Maybe | ||||||
|  | -- | ||||||
|  | import qualified Control.Exception as C | ||||||
|  | -- import Control.Monad.Except | ||||||
|  | import Data.List | ||||||
|  | -- import Data.Maybe | ||||||
|  | import System.Directory (doesFileExist, getHomeDirectory) | ||||||
|  | import System.Environment (getEnv) | ||||||
|  | import System.Exit (exitFailure) | ||||||
|  | import System.FilePath ((</>)) | ||||||
|  | import System.IO (IOMode(..), openFile, stdin, stderr, hSetNewlineMode, universalNewlineMode) | ||||||
|  | import Test.HUnit | ||||||
|  | import Text.Printf | ||||||
|  | 
 | ||||||
|  | import Hledger.Data.Dates (getCurrentDay) | ||||||
|  | import Hledger.Data.Journal () -- Show instance | ||||||
|  | import Hledger.Data.Types | ||||||
|  | import Hledger.Read.JournalReader as JournalReader | ||||||
|  | import Hledger.Read.TimedotReader as TimedotReader | ||||||
|  | import Hledger.Read.TimelogReader as TimelogReader | ||||||
|  | import Hledger.Read.CsvReader as CsvReader | ||||||
|  | import Hledger.Utils | ||||||
|  | import Prelude hiding (getContents, writeFile) | ||||||
|  | import Hledger.Utils.UTF8IOCompat (hGetContents, writeFile) | ||||||
|  | 
 | ||||||
|  | 
 | ||||||
|  | journalEnvVar           = "LEDGER_FILE" | ||||||
|  | journalEnvVar2          = "LEDGER" | ||||||
|  | journalDefaultFilename  = ".hledger.journal" | ||||||
|  | 
 | ||||||
|  | -- The available data file readers, each one handling a particular data | ||||||
|  | -- format. The first is also used as the default for unknown formats. | ||||||
|  | readers :: [Reader] | ||||||
|  | readers = [ | ||||||
|  |   JournalReader.reader | ||||||
|  |  ,TimelogReader.reader | ||||||
|  |  ,TimedotReader.reader | ||||||
|  |  ,CsvReader.reader | ||||||
|  |  ] | ||||||
|  | 
 | ||||||
|  | -- | Which readers are worth trying for this (possibly unspecified) format, filepath, and data ? | ||||||
|  | readersFor :: (Maybe StorageFormat, Maybe FilePath, String) -> [Reader] | ||||||
|  | readersFor (format,path,s) = | ||||||
|  |     dbg1 ("possible readers for "++show (format,path,elideRight 30 s)) $ | ||||||
|  |     case format of | ||||||
|  |      Just f  -> case readerForStorageFormat f of Just r  -> [r] | ||||||
|  |                                                  Nothing -> [] | ||||||
|  |      Nothing -> case path of Nothing  -> readers | ||||||
|  |                              Just p   -> case readersForPathAndData (p,s) of [] -> readers | ||||||
|  |                                                                              rs -> rs | ||||||
|  | 
 | ||||||
|  | -- | Find the (first) reader which can handle the given format, if any. | ||||||
|  | readerForStorageFormat :: StorageFormat -> Maybe Reader | ||||||
|  | readerForStorageFormat s | null rs = Nothing | ||||||
|  |                   | otherwise = Just $ head rs | ||||||
|  |     where | ||||||
|  |       rs = filter ((s==).rFormat) readers :: [Reader] | ||||||
|  | 
 | ||||||
|  | -- | Find the readers which think they can handle the given file path and data, if any. | ||||||
|  | readersForPathAndData :: (FilePath,String) -> [Reader] | ||||||
|  | readersForPathAndData (f,s) = filter (\r -> (rDetector r) f s) readers | ||||||
|  | 
 | ||||||
|  | -- try each reader in turn, returning the error of the first if all fail | ||||||
|  | tryReaders :: [Reader] -> Maybe FilePath -> Bool -> Maybe FilePath -> String -> IO (Either String Journal) | ||||||
|  | tryReaders readers mrulesfile assrt path s = firstSuccessOrBestError [] readers | ||||||
|  |   where | ||||||
|  |     firstSuccessOrBestError :: [String] -> [Reader] -> IO (Either String Journal) | ||||||
|  |     firstSuccessOrBestError [] []        = return $ Left "no readers found" | ||||||
|  |     firstSuccessOrBestError errs (r:rs) = do | ||||||
|  |       dbg1IO "trying reader" (rFormat r) | ||||||
|  |       result <- (runExceptT . (rParser r) mrulesfile assrt path') s | ||||||
|  |       dbg1IO "reader result" $ either id show result | ||||||
|  |       case result of Right j -> return $ Right j                       -- success! | ||||||
|  |                      Left e  -> firstSuccessOrBestError (errs++[e]) rs -- keep trying | ||||||
|  |     firstSuccessOrBestError (e:_) []    = return $ Left e              -- none left, return first error | ||||||
|  |     path' = fromMaybe "(string)" path | ||||||
|  | 
 | ||||||
|  | 
 | ||||||
|  | -- | Read a journal from this string, trying whatever readers seem appropriate: | ||||||
|  | -- | ||||||
|  | -- - if a format is specified, try that reader only | ||||||
|  | -- | ||||||
|  | -- - or if one or more readers recognises the file path and data, try those | ||||||
|  | -- | ||||||
|  | -- - otherwise, try them all. | ||||||
|  | -- | ||||||
|  | -- A CSV conversion rules file may also be specified for use by the CSV reader. | ||||||
|  | -- Also there is a flag specifying whether to check or ignore balance assertions in the journal. | ||||||
|  | readJournal :: Maybe StorageFormat -> Maybe FilePath -> Bool -> Maybe FilePath -> String -> IO (Either String Journal) | ||||||
|  | readJournal mformat mrulesfile assrt path s = tryReaders (readersFor (mformat, path, s)) mrulesfile assrt path s | ||||||
|  | 
 | ||||||
|  | -- | Read a Journal from this file (or stdin if the filename is -) or give | ||||||
|  | -- an error message, using the specified data format or trying all known | ||||||
|  | -- formats. A CSV conversion rules file may be specified for better | ||||||
|  | -- conversion of that format. Also there is a flag specifying whether | ||||||
|  | -- to check or ignore balance assertions in the journal. | ||||||
|  | readJournalFile :: Maybe StorageFormat -> Maybe FilePath -> Bool -> FilePath -> IO (Either String Journal) | ||||||
|  | readJournalFile format rulesfile assrt f = readJournalFiles format rulesfile assrt [f] | ||||||
|  | 
 | ||||||
|  | readJournalFiles :: Maybe StorageFormat -> Maybe FilePath -> Bool -> [FilePath] -> IO (Either String Journal) | ||||||
|  | readJournalFiles format rulesfile assrt f = do | ||||||
|  |   contents <- fmap concat $ mapM readFileAnyNewline f | ||||||
|  |   readJournal format rulesfile assrt (listToMaybe f) contents | ||||||
|  |  where | ||||||
|  |   readFileAnyNewline f = do | ||||||
|  |     requireJournalFileExists f | ||||||
|  |     h <- fileHandle f | ||||||
|  |     hSetNewlineMode h universalNewlineMode | ||||||
|  |     hGetContents h | ||||||
|  |   fileHandle "-" = return stdin | ||||||
|  |   fileHandle f = openFile f ReadMode | ||||||
|  | 
 | ||||||
|  | -- | If the specified journal file does not exist, give a helpful error and quit. | ||||||
|  | requireJournalFileExists :: FilePath -> IO () | ||||||
|  | requireJournalFileExists "-" = return () | ||||||
|  | requireJournalFileExists f = do | ||||||
|  |   exists <- doesFileExist f | ||||||
|  |   when (not exists) $ do | ||||||
|  |     hPrintf stderr "The hledger journal file \"%s\" was not found.\n" f | ||||||
|  |     hPrintf stderr "Please create it first, eg with \"hledger add\" or a text editor.\n" | ||||||
|  |     hPrintf stderr "Or, specify an existing journal file with -f or LEDGER_FILE.\n" | ||||||
|  |     exitFailure | ||||||
|  | 
 | ||||||
|  | -- | Ensure there is a journal file at the given path, creating an empty one if needed. | ||||||
|  | ensureJournalFileExists :: FilePath -> IO () | ||||||
|  | ensureJournalFileExists f = do | ||||||
|  |   exists <- doesFileExist f | ||||||
|  |   when (not exists) $ do | ||||||
|  |     hPrintf stderr "Creating hledger journal file %s.\n" f | ||||||
|  |     -- note Hledger.Utils.UTF8.* do no line ending conversion on windows, | ||||||
|  |     -- we currently require unix line endings on all platforms. | ||||||
|  |     newJournalContent >>= writeFile f | ||||||
|  | 
 | ||||||
|  | -- | Give the content for a new auto-created journal file. | ||||||
|  | newJournalContent :: IO String | ||||||
|  | newJournalContent = do | ||||||
|  |   d <- getCurrentDay | ||||||
|  |   return $ printf "; journal created %s by hledger\n" (show d) | ||||||
|  | 
 | ||||||
|  | -- | Get the default journal file path specified by the environment. | ||||||
|  | -- Like ledger, we look first for the LEDGER_FILE environment | ||||||
|  | -- variable, and if that does not exist, for the legacy LEDGER | ||||||
|  | -- environment variable. If neither is set, or the value is blank, | ||||||
|  | -- return the hard-coded default, which is @.hledger.journal@ in the | ||||||
|  | -- users's home directory (or in the current directory, if we cannot | ||||||
|  | -- determine a home directory). | ||||||
|  | defaultJournalPath :: IO String | ||||||
|  | defaultJournalPath = do | ||||||
|  |   s <- envJournalPath | ||||||
|  |   if null s then defaultJournalPath else return s | ||||||
|  |     where | ||||||
|  |       envJournalPath = | ||||||
|  |         getEnv journalEnvVar | ||||||
|  |          `C.catch` (\(_::C.IOException) -> getEnv journalEnvVar2 | ||||||
|  |                                             `C.catch` (\(_::C.IOException) -> return "")) | ||||||
|  |       defaultJournalPath = do | ||||||
|  |                   home <- getHomeDirectory `C.catch` (\(_::C.IOException) -> return "") | ||||||
|  |                   return $ home </> journalDefaultFilename | ||||||
|  | 
 | ||||||
|  | -- | Read the default journal file specified by the environment, or raise an error. | ||||||
|  | defaultJournal :: IO Journal | ||||||
|  | defaultJournal = defaultJournalPath >>= readJournalFile Nothing Nothing True >>= either error' return | ||||||
|  | 
 | ||||||
|  | -- | Read a journal from the given string, trying all known formats, or simply throw an error. | ||||||
|  | readJournal' :: String -> IO Journal | ||||||
|  | readJournal' s = readJournal Nothing Nothing True Nothing s >>= either error' return | ||||||
|  | 
 | ||||||
|  | tests_readJournal' = [ | ||||||
|  |   "readJournal' parses sample journal" ~: do | ||||||
|  |      _ <- samplejournal | ||||||
|  |      assertBool "" True | ||||||
|  |  ] | ||||||
|  | 
 | ||||||
|  | -- tests | ||||||
|  | 
 | ||||||
|  | samplejournal = readJournal' $ unlines | ||||||
|  |  ["2008/01/01 income" | ||||||
|  |  ,"    assets:bank:checking  $1" | ||||||
|  |  ,"    income:salary" | ||||||
|  |  ,"" | ||||||
|  |  ,"comment" | ||||||
|  |  ,"multi line comment here" | ||||||
|  |  ,"for testing purposes" | ||||||
|  |  ,"end comment" | ||||||
|  |  ,"" | ||||||
|  |  ,"2008/06/01 gift" | ||||||
|  |  ,"    assets:bank:checking  $1" | ||||||
|  |  ,"    income:gifts" | ||||||
|  |  ,"" | ||||||
|  |  ,"2008/06/02 save" | ||||||
|  |  ,"    assets:bank:saving  $1" | ||||||
|  |  ,"    assets:bank:checking" | ||||||
|  |  ,"" | ||||||
|  |  ,"2008/06/03 * eat & shop" | ||||||
|  |  ,"    expenses:food      $1" | ||||||
|  |  ,"    expenses:supplies  $1" | ||||||
|  |  ,"    assets:cash" | ||||||
|  |  ,"" | ||||||
|  |  ,"2008/12/31 * pay off" | ||||||
|  |  ,"    liabilities:debts  $1" | ||||||
|  |  ,"    assets:bank:checking" | ||||||
|  |  ] | ||||||
| @ -102,6 +102,7 @@ library | |||||||
|       Hledger.Read |       Hledger.Read | ||||||
|       Hledger.Read.CsvReader |       Hledger.Read.CsvReader | ||||||
|       Hledger.Read.JournalReader |       Hledger.Read.JournalReader | ||||||
|  |       Hledger.Read.TimedotReader | ||||||
|       Hledger.Read.TimelogReader |       Hledger.Read.TimelogReader | ||||||
|       Hledger.Reports |       Hledger.Reports | ||||||
|       Hledger.Reports.ReportOptions |       Hledger.Reports.ReportOptions | ||||||
|  | |||||||
							
								
								
									
										84
									
								
								hledger-lib/hledger_timedot.5.md
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										84
									
								
								hledger-lib/hledger_timedot.5.md
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,84 @@ | |||||||
|  | % hledger_timedot(5) | ||||||
|  | % | ||||||
|  | % February 2016 | ||||||
|  | 
 | ||||||
|  | # NAME | ||||||
|  | 
 | ||||||
|  | hledger_timedot - time logging format | ||||||
|  | 
 | ||||||
|  | # DESCRIPTION | ||||||
|  | 
 | ||||||
|  | Timedot is a plain text format for logging dated, categorised quantities (eg time), supported by hledger. | ||||||
|  | It is convenient for approximate and retroactive time logging, | ||||||
|  | eg when the real-time clock-in/out required with a timeclock file is too precise or too interruptive. | ||||||
|  | It can be formatted like a bar chart, making clear at a glance where time was spent. | ||||||
|  | 
 | ||||||
|  | Though called "timedot", the format does not specify the commodity being logged, so could represent other dated, quantifiable things. | ||||||
|  | Eg you could record a single-entry journal of financial transactions, perhaps slightly more conveniently than with hledger_journal(5) format. | ||||||
|  | 
 | ||||||
|  | ## Format | ||||||
|  | 
 | ||||||
|  | A timedot file contains a series of day entries. | ||||||
|  | A day entry begins with a date, and is followed by category/quantity pairs, one per line. | ||||||
|  | Dates are hledger-style [simple date](#simple-dates) (see hledger_journal(5)). | ||||||
|  | Categories are hledger-style account names, optionally indented. | ||||||
|  | There must be at least two spaces between the category and the quantity. | ||||||
|  | Quantities can be written in two ways: | ||||||
|  | 
 | ||||||
|  | 1. a series of dots (period characters). | ||||||
|  |    Each dot represents "a quarter" - eg, a quarter hour. | ||||||
|  |    Spaces can be used to group dots into hours, for easier counting. | ||||||
|  | 
 | ||||||
|  | 2. a number (integer or decimal), representing "units" - eg, hours. | ||||||
|  |    A good alternative when dots are cumbersome. | ||||||
|  |    (A number also can record negative quantities.) | ||||||
|  | 
 | ||||||
|  | Blank lines and lines beginning with #, ; or * are ignored. | ||||||
|  | An example: | ||||||
|  | 
 | ||||||
|  | ```timedot | ||||||
|  | # on this day, 6h was spent on client work, 1.5h on haskell FOSS work, etc. | ||||||
|  | 2016/2/1 | ||||||
|  | inc:client1   .... .... .... .... .... .... | ||||||
|  | fos:haskell   .... ..  | ||||||
|  | biz:research  . | ||||||
|  | 
 | ||||||
|  | 2016/2/2 | ||||||
|  | inc:client1   .... .... | ||||||
|  | biz:research  . | ||||||
|  | ``` | ||||||
|  | 
 | ||||||
|  | Or with numbers: | ||||||
|  | 
 | ||||||
|  | ```timedot | ||||||
|  | 2016/2/1 | ||||||
|  | inc:client1   6 | ||||||
|  | fos:haskell   1.5 | ||||||
|  | biz:research  .25 | ||||||
|  | ``` | ||||||
|  | 
 | ||||||
|  | I prefer . (period) for separating account components: | ||||||
|  | 
 | ||||||
|  | ```timedot | ||||||
|  | 2016/2/3 | ||||||
|  | fos.hledger.timedot  4 | ||||||
|  | biz.research         1 | ||||||
|  | ``` | ||||||
|  | 
 | ||||||
|  | hledger requires : (colon), so rewrite them with --alias: | ||||||
|  | 
 | ||||||
|  | ```shell | ||||||
|  | $ hledger -f t.timedot --alias /\\./=: bal -W | ||||||
|  | ``` | ||||||
|  | 
 | ||||||
|  | [default year directives](#default-year) may be used. | ||||||
|  | 
 | ||||||
|  | Here is a | ||||||
|  | [sample.timedot](https://raw.github.com/simonmichael/hledger/master/data/sample.timedot). | ||||||
|  | <!-- to download and some queries to try: --> | ||||||
|  | 
 | ||||||
|  | <!-- ```shell --> | ||||||
|  | <!-- $ hledger -f sample.timedot balance                               # current time balances --> | ||||||
|  | <!-- $ hledger -f sample.timedot register -p 2009/3                    # sessions in march 2009 --> | ||||||
|  | <!-- $ hledger -f sample.timedot register -p weekly --depth 1 --empty  # time summary by week --> | ||||||
|  | <!-- ``` --> | ||||||
| @ -113,6 +113,7 @@ library: | |||||||
|     - Hledger.Read |     - Hledger.Read | ||||||
|     - Hledger.Read.CsvReader |     - Hledger.Read.CsvReader | ||||||
|     - Hledger.Read.JournalReader |     - Hledger.Read.JournalReader | ||||||
|  |     - Hledger.Read.TimedotReader | ||||||
|     - Hledger.Read.TimelogReader |     - Hledger.Read.TimelogReader | ||||||
|     - Hledger.Reports |     - Hledger.Reports | ||||||
|     - Hledger.Reports.ReportOptions |     - Hledger.Reports.ReportOptions | ||||||
|  | |||||||
| @ -787,7 +787,7 @@ it may only include other journal files (eg, not CSV or timelog files.) | |||||||
| 
 | 
 | ||||||
| ### Timelog | ### Timelog | ||||||
| 
 | 
 | ||||||
| hledger can also read timelog files. | hledger can also read timelog (aka timeclock) files. | ||||||
| [As with Ledger](http://ledger-cli.org/3.0/doc/ledger3.html#Time-Keeping), | [As with Ledger](http://ledger-cli.org/3.0/doc/ledger3.html#Time-Keeping), | ||||||
| these are (a subset of) | these are (a subset of) | ||||||
| [timeclock.el](http://www.emacswiki.org/emacs/TimeClock)'s format, | [timeclock.el](http://www.emacswiki.org/emacs/TimeClock)'s format, | ||||||
| @ -846,6 +846,77 @@ To generate time logs, ie to clock in and clock out, you could: | |||||||
| - or use the old `ti` and `to` scripts in the [ledger 2.x repository](https://github.com/ledger/ledger/tree/release/2.6.3/scripts). | - or use the old `ti` and `to` scripts in the [ledger 2.x repository](https://github.com/ledger/ledger/tree/release/2.6.3/scripts). | ||||||
|   These rely on a "timeclock" executable which I think is just the ledger 2 executable renamed. |   These rely on a "timeclock" executable which I think is just the ledger 2 executable renamed. | ||||||
| 
 | 
 | ||||||
|  | 
 | ||||||
|  | ### Timedot | ||||||
|  | 
 | ||||||
|  | Timedot is another time-logging format supported by hledger. | ||||||
|  | It is convenient for approximate and retroactive time logging, | ||||||
|  | eg when the real-time clock-in/out required with a timeclock file is too precise or too interruptive. | ||||||
|  | It can be formatted like a bar chart, making clear at a glance where time was spent. | ||||||
|  | 
 | ||||||
|  | Though called "timedot", the format does not specify the commodity being logged, so could represent other dated, quantifiable things. | ||||||
|  | Eg you could record a single-entry journal of financial transactions, perhaps slightly more conveniently than with hledger_journal(5) format. | ||||||
|  | 
 | ||||||
|  | ## Format | ||||||
|  | 
 | ||||||
|  | A timedot file contains a series of day entries. | ||||||
|  | A day entry begins with a date, and is followed by category/quantity pairs, one per line. | ||||||
|  | Dates are hledger-style [simple date](#simple-dates) (see hledger_journal(5)). | ||||||
|  | Categories are hledger-style account names, optionally indented. | ||||||
|  | There must be at least two spaces between the category and the quantity. | ||||||
|  | Quantities can be written in two ways: | ||||||
|  | 
 | ||||||
|  | 1. a series of dots (period characters). | ||||||
|  |    Each dot represents "a quarter" - eg, a quarter hour. | ||||||
|  |    Spaces can be used to group dots into hours, for easier counting. | ||||||
|  | 
 | ||||||
|  | 2. a number (integer or decimal), representing "units" - eg, hours. | ||||||
|  |    A good alternative when dots are cumbersome. | ||||||
|  |    (A number also can record negative quantities.) | ||||||
|  | 
 | ||||||
|  | Blank lines and lines beginning with #, ; or * are ignored. | ||||||
|  | An example: | ||||||
|  | 
 | ||||||
|  | ```timedot | ||||||
|  | # on this day, 6h was spent on client work, 1.5h on haskell FOSS work, etc. | ||||||
|  | 2016/2/1 | ||||||
|  | inc:client1   .... .... .... .... .... .... | ||||||
|  | fos:haskell   .... ..  | ||||||
|  | biz:research  . | ||||||
|  | 
 | ||||||
|  | 2016/2/2 | ||||||
|  | inc:client1   .... .... | ||||||
|  | biz:research  . | ||||||
|  | ``` | ||||||
|  | 
 | ||||||
|  | Or with numbers: | ||||||
|  | 
 | ||||||
|  | ```timedot | ||||||
|  | 2016/2/1 | ||||||
|  | inc:client1   6 | ||||||
|  | fos:haskell   1.5 | ||||||
|  | biz:research  .25 | ||||||
|  | ``` | ||||||
|  | 
 | ||||||
|  | I prefer . (period) for separating account components: | ||||||
|  | 
 | ||||||
|  | ```timedot | ||||||
|  | 2016/2/3 | ||||||
|  | fos.hledger.timedot  4 | ||||||
|  | biz.research         1 | ||||||
|  | ``` | ||||||
|  | 
 | ||||||
|  | hledger requires : (colon), so rewrite them with --alias: | ||||||
|  | 
 | ||||||
|  | ```shell | ||||||
|  | $ hledger -f t.timedot --alias /\\./=: bal -W | ||||||
|  | ``` | ||||||
|  | 
 | ||||||
|  | [default year directives](#default-year) may be used. | ||||||
|  | 
 | ||||||
|  | Here is a | ||||||
|  | [sample.timedot](https://raw.github.com/simonmichael/hledger/master/data/sample.timedot). | ||||||
|  | 
 | ||||||
| ### CSV | ### CSV | ||||||
| 
 | 
 | ||||||
| hledger can also read | hledger can also read | ||||||
|  | |||||||
		Loading…
	
		Reference in New Issue
	
	Block a user