rename timelog format to timeclock

This commit is contained in:
Simon Michael 2016-04-12 21:10:02 -07:00
parent 3e53cf7ef9
commit 588f36d662
36 changed files with 140 additions and 140 deletions

View File

@ -356,7 +356,7 @@ hledgercov: \
$(call def-help,hledgercov, build "bin/hledgercov" for coverage reports (with ghc) ) $(call def-help,hledgercov, build "bin/hledgercov" for coverage reports (with ghc) )
$(GHC) $(MAIN) -fhpc -o bin/hledgercov -outputdir .hledgercovobjs $(BUILDFLAGS) $(GHC) $(MAIN) -fhpc -o bin/hledgercov -outputdir .hledgercovobjs $(BUILDFLAGS)
# hledger-lib/Hledger/Read/TimelogReaderPP.hs # hledger-lib/Hledger/Read/TimeclockReaderPP.hs
dev: dev.hs $(SOURCEFILES) \ dev: dev.hs $(SOURCEFILES) \
$(call def-help,dev, build the dev.hs script for quick experiments (with ghc) ) $(call def-help,dev, build the dev.hs script for quick experiments (with ghc) )
stack ghc -- $(CABALMACROSFLAGS) -ihledger-lib dev.hs \ stack ghc -- $(CABALMACROSFLAGS) -ihledger-lib dev.hs \
@ -1047,7 +1047,7 @@ haddock: \
MANPAGES=\ 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_timeclock.5 \
hledger-lib/hledger_timedot.5 \ hledger-lib/hledger_timedot.5 \
hledger/hledger.1 \ hledger/hledger.1 \
hledger-ui/hledger-ui.1 \ hledger-ui/hledger-ui.1 \

View File

@ -107,7 +107,7 @@ main = do
,"hledger-api.1" ,"hledger-api.1"
,"hledger_journal.5" ,"hledger_journal.5"
,"hledger_csv.5" ,"hledger_csv.5"
,"hledger_timelog.5" ,"hledger_timeclock.5"
,"hledger_timedot.5" ,"hledger_timedot.5"
] ]

20
dev.hs
View File

@ -16,9 +16,9 @@ import Hledger
-- import Hledger.Utils.Regex (toRegexCI) -- import Hledger.Utils.Regex (toRegexCI)
-- import Hledger.Utils.Debug -- import Hledger.Utils.Debug
-- import qualified Hledger.Read.JournalReader as JR -- import qualified Hledger.Read.JournalReader as JR
-- import qualified Hledger.Read.TimelogReader as TR -- import qualified Hledger.Read.TimeclockReader as TR
-- import qualified Hledger.Read.TimelogReaderNoJU as TRNOJU -- import qualified Hledger.Read.TimeclockReaderNoJU as TRNOJU
-- import qualified Hledger.Read.TimelogReaderPP as TRPP -- import qualified Hledger.Read.TimeclockReaderPP as TRPP
-- import Control.DeepSeq (NFData) -- import Control.DeepSeq (NFData)
-- import Data.Data -- import Data.Data
@ -36,7 +36,7 @@ journal =
-- "data/10000x1000x10.journal" -- "data/10000x1000x10.journal"
"data/10000x1000x10.journal" "data/10000x1000x10.journal"
timelog = "data/sample.timelog" timeclock = "data/sample.timeclock"
timeit :: String -> IO a -> IO (Double, a) timeit :: String -> IO a -> IO (Double, a)
timeit name action = do timeit name action = do
@ -131,8 +131,8 @@ main = do
-- return () -- return ()
-- benchmark timelog parsing -- benchmark timeclock parsing
-- s <- readFile inputtimelog -- s <- readFile inputtimeclock
-- putStrLn $ show $ length s -- putStrLn $ show $ length s
-- let s = unlines [ -- let s = unlines [
-- "i 2009/03/27 09:00:00 projects:a", -- "i 2009/03/27 09:00:00 projects:a",
@ -144,11 +144,11 @@ main = do
-- ] -- ]
-- -- let output = return . const -- putStrLn.show -- -- let output = return . const -- putStrLn.show
-- -- withArgs ["-l"] $ defaultMain [bench "timelog polyparse" $ nfIO $ runExceptT $ TRPP.parseJournalWith' TRPP.timelogFile False "" s] -- -- withArgs ["-l"] $ defaultMain [bench "timeclock polyparse" $ nfIO $ runExceptT $ TRPP.parseJournalWith' TRPP.timeclockFile False "" s]
-- defaultMain [ -- defaultMain [
-- -- bench ("read "++inputtimelog++" with parsec") $ nfIO $ runExceptT (TR.parse Nothing False "" s) >>= output -- -- bench ("read "++inputtimeclock++" with parsec") $ nfIO $ runExceptT (TR.parse Nothing False "" s) >>= output
-- -- bench ("read "++inputtimelog++" with parsec, no ju") $ nfIO $ runExceptT (TRNOJU.parse Nothing False "" s) >>= output, -- -- bench ("read "++inputtimeclock++" with parsec, no ju") $ nfIO $ runExceptT (TRNOJU.parse Nothing False "" s) >>= output,
-- -- bench ("read "++inputtimelog++" polyparse") $ nfIO $ runExceptT (TRPP.parse Nothing False "" s) >>= output -- -- bench ("read "++inputtimeclock++" polyparse") $ nfIO $ runExceptT (TRPP.parse Nothing False "" s) >>= output
-- ] -- ]
-- return () -- return ()

View File

@ -32,7 +32,7 @@ Copyright (C) 2007-2015 Simon Michael.
Released under GNU GPLv3+. Released under GNU GPLv3+.
.SH SEE ALSO .SH SEE ALSO
hledger(1), hledger\-ui(1), hledger\-web(1), ledger(1) hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1)
.br hledger_csv(5), hledger_journal(5), hledger_timeclock(5)
hledger_csv(5), hledger_journal(5), hledger_timelog(5) ledger(1)
--> -->

View File

@ -37,7 +37,7 @@ Released under GNU GPL v3 or later.
.SH SEE ALSO .SH SEE ALSO
hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1), hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1),
hledger_csv(5), hledger_journal(5), hledger_timelog(5), hledger_timedot(5), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_timedot(5),
ledger(1) ledger(1)
http://hledger.org http://hledger.org

View File

@ -65,7 +65,7 @@ Released under GNU GPL v3 or later.
.SH SEE ALSO .SH SEE ALSO
hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1), hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1),
hledger_csv(5), hledger_journal(5), hledger_timelog(5), hledger_timedot(5), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_timedot(5),
ledger(1) ledger(1)
http://hledger.org http://hledger.org

View File

@ -38,7 +38,7 @@ Note there is no built-in access control, so you will need to hide
hledger-api behind an authenticating proxy if you want to restrict hledger-api behind an authenticating proxy if you want to restrict
access. access.
<!-- With journal and timelog files (but not CSV files, currently) --> <!-- With journal and timeclock files (but not CSV files, currently) -->
<!-- the web app detects changes and will show the new data on the next request. --> <!-- the web app detects changes and will show the new data on the next request. -->
<!-- If a change makes the file unparseable, hledger-api will show an error --> <!-- If a change makes the file unparseable, hledger-api will show an error -->
<!-- until the file has been fixed. --> <!-- until the file has been fixed. -->

View File

@ -18,7 +18,7 @@ module Hledger.Data (
module Hledger.Data.Posting, module Hledger.Data.Posting,
module Hledger.Data.RawOptions, module Hledger.Data.RawOptions,
module Hledger.Data.StringFormat, module Hledger.Data.StringFormat,
module Hledger.Data.TimeLog, module Hledger.Data.Timeclock,
module Hledger.Data.Transaction, module Hledger.Data.Transaction,
module Hledger.Data.Types, module Hledger.Data.Types,
tests_Hledger_Data tests_Hledger_Data
@ -36,7 +36,7 @@ import Hledger.Data.Ledger
import Hledger.Data.Posting import Hledger.Data.Posting
import Hledger.Data.RawOptions import Hledger.Data.RawOptions
import Hledger.Data.StringFormat import Hledger.Data.StringFormat
import Hledger.Data.TimeLog import Hledger.Data.Timeclock
import Hledger.Data.Transaction import Hledger.Data.Transaction
import Hledger.Data.Types import Hledger.Data.Types
@ -53,7 +53,7 @@ tests_Hledger_Data = TestList
,tests_Hledger_Data_Posting ,tests_Hledger_Data_Posting
-- ,tests_Hledger_Data_RawOptions -- ,tests_Hledger_Data_RawOptions
-- ,tests_Hledger_Data_StringFormat -- ,tests_Hledger_Data_StringFormat
,tests_Hledger_Data_TimeLog ,tests_Hledger_Data_Timeclock
,tests_Hledger_Data_Transaction ,tests_Hledger_Data_Transaction
-- ,tests_Hledger_Data_Types -- ,tests_Hledger_Data_Types
] ]

View File

@ -12,7 +12,7 @@ module Hledger.Data.Journal (
addMarketPrice, addMarketPrice,
addModifierTransaction, addModifierTransaction,
addPeriodicTransaction, addPeriodicTransaction,
addTimeLogEntry, addTimeclockEntry,
addTransaction, addTransaction,
journalApplyAliases, journalApplyAliases,
journalBalanceTransactions, journalBalanceTransactions,
@ -81,7 +81,7 @@ import Hledger.Data.Amount
import Hledger.Data.Dates import Hledger.Data.Dates
import Hledger.Data.Transaction import Hledger.Data.Transaction
import Hledger.Data.Posting import Hledger.Data.Posting
import Hledger.Data.TimeLog import Hledger.Data.Timeclock
import Hledger.Query import Hledger.Query
@ -116,7 +116,7 @@ instance Show Journal where
-- ,show (jtxns j) -- ,show (jtxns j)
-- ,show (jmodifiertxns j) -- ,show (jmodifiertxns j)
-- ,show (jperiodictxns j) -- ,show (jperiodictxns j)
-- ,show $ open_timelog_entries j -- ,show $ open_timeclock_entries j
-- ,show $ jmarketprices j -- ,show $ jmarketprices j
-- ,show $ final_comment_lines j -- ,show $ final_comment_lines j
-- ,show $ jContext j -- ,show $ jContext j
@ -127,7 +127,7 @@ nulljournal :: Journal
nulljournal = Journal { jmodifiertxns = [] nulljournal = Journal { jmodifiertxns = []
, jperiodictxns = [] , jperiodictxns = []
, jtxns = [] , jtxns = []
, open_timelog_entries = [] , open_timeclock_entries = []
, jmarketprices = [] , jmarketprices = []
, final_comment_lines = [] , final_comment_lines = []
, jContext = nullctx , jContext = nullctx
@ -160,8 +160,8 @@ addPeriodicTransaction pt j = j { jperiodictxns = pt : jperiodictxns j }
addMarketPrice :: MarketPrice -> Journal -> Journal addMarketPrice :: MarketPrice -> Journal -> Journal
addMarketPrice h j = j { jmarketprices = h : jmarketprices j } addMarketPrice h j = j { jmarketprices = h : jmarketprices j }
addTimeLogEntry :: TimeLogEntry -> Journal -> Journal addTimeclockEntry :: TimeclockEntry -> Journal -> Journal
addTimeLogEntry tle j = j { open_timelog_entries = tle : open_timelog_entries j } addTimeclockEntry tle j = j { open_timeclock_entries = tle : open_timeclock_entries j }
-- | Get the transaction with this index (its 1-based position in the input stream), if any. -- | Get the transaction with this index (its 1-based position in the input stream), if any.
journalTransactionAt :: Journal -> Integer -> Maybe Transaction journalTransactionAt :: Journal -> Integer -> Maybe Transaction
@ -416,12 +416,12 @@ journalApplyAliases aliases j@Journal{jtxns=ts} =
-- | Do post-parse processing on a journal to make it ready for use: check -- | Do post-parse processing on a journal to make it ready for use: check
-- all transactions balance, canonicalise amount formats, close any open -- all transactions balance, canonicalise amount formats, close any open
-- timelog entries, maybe check balance assertions and so on. -- timeclock entries, maybe check balance assertions and so on.
journalFinalise :: ClockTime -> LocalTime -> FilePath -> String -> JournalContext -> Bool -> Journal -> Either String Journal journalFinalise :: ClockTime -> LocalTime -> FilePath -> String -> JournalContext -> Bool -> Journal -> Either String Journal
journalFinalise tclock tlocal path txt ctx assrt j@Journal{files=fs} = do journalFinalise tclock tlocal path txt ctx assrt j@Journal{files=fs} = do
(journalBalanceTransactions $ (journalBalanceTransactions $
journalApplyCommodityStyles $ journalApplyCommodityStyles $
journalCloseTimeLogEntries tlocal $ journalCloseTimeclockEntries tlocal $
j{ files=(path,txt):fs j{ files=(path,txt):fs
, filereadtime=tclock , filereadtime=tclock
, jContext=ctx , jContext=ctx
@ -429,7 +429,7 @@ journalFinalise tclock tlocal path txt ctx assrt j@Journal{files=fs} = do
, jmodifiertxns=reverse $ jmodifiertxns j -- NOTE: see addModifierTransaction , jmodifiertxns=reverse $ jmodifiertxns j -- NOTE: see addModifierTransaction
, jperiodictxns=reverse $ jperiodictxns j -- NOTE: see addPeriodicTransaction , jperiodictxns=reverse $ jperiodictxns j -- NOTE: see addPeriodicTransaction
, jmarketprices=reverse $ jmarketprices j -- NOTE: see addMarketPrice , jmarketprices=reverse $ jmarketprices j -- NOTE: see addMarketPrice
, open_timelog_entries=reverse $ open_timelog_entries j -- NOTE: see addTimeLogEntry , open_timeclock_entries=reverse $ open_timeclock_entries j -- NOTE: see addTimeclockEntry
}) })
>>= if assrt then journalCheckBalanceAssertions else return >>= if assrt then journalCheckBalanceAssertions else return
@ -597,10 +597,10 @@ canonicalStyleFrom ss@(first:_) =
-- case ps of (MarketPrice{mpamount=a}:_) -> Just a -- case ps of (MarketPrice{mpamount=a}:_) -> Just a
-- _ -> Nothing -- _ -> Nothing
-- | Close any open timelog sessions in this journal using the provided current time. -- | Close any open timeclock sessions in this journal using the provided current time.
journalCloseTimeLogEntries :: LocalTime -> Journal -> Journal journalCloseTimeclockEntries :: LocalTime -> Journal -> Journal
journalCloseTimeLogEntries now j@Journal{jtxns=ts, open_timelog_entries=es} = journalCloseTimeclockEntries now j@Journal{jtxns=ts, open_timeclock_entries=es} =
j{jtxns = ts ++ (timeLogEntriesToTransactions now es), open_timelog_entries = []} j{jtxns = ts ++ (timeclockEntriesToTransactions now es), open_timeclock_entries = []}
-- | Convert all this journal's amounts to cost by applying their prices, if any. -- | Convert all this journal's amounts to cost by applying their prices, if any.
journalConvertAmountsToCost :: Journal -> Journal journalConvertAmountsToCost :: Journal -> Journal

View File

@ -1,13 +1,13 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
{-| {-|
A 'TimeLogEntry' is a clock-in, clock-out, or other directive in a timelog A 'TimeclockEntry' is a clock-in, clock-out, or other directive in a timeclock
file (see timeclock.el or the command-line version). These can be file (see timeclock.el or the command-line version). These can be
converted to 'Transactions' and queried like a ledger. converted to 'Transactions' and queried like a ledger.
-} -}
module Hledger.Data.TimeLog module Hledger.Data.Timeclock
where where
import Data.Maybe import Data.Maybe
import Data.Time.Calendar import Data.Time.Calendar
@ -27,17 +27,17 @@ import Hledger.Data.Amount
import Hledger.Data.Posting import Hledger.Data.Posting
import Hledger.Data.Transaction import Hledger.Data.Transaction
instance Show TimeLogEntry where instance Show TimeclockEntry where
show t = printf "%s %s %s %s" (show $ tlcode t) (show $ tldatetime t) (tlaccount t) (tldescription t) show t = printf "%s %s %s %s" (show $ tlcode t) (show $ tldatetime t) (tlaccount t) (tldescription t)
instance Show TimeLogCode where instance Show TimeclockCode where
show SetBalance = "b" show SetBalance = "b"
show SetRequiredHours = "h" show SetRequiredHours = "h"
show In = "i" show In = "i"
show Out = "o" show Out = "o"
show FinalOut = "O" show FinalOut = "O"
instance Read TimeLogCode where instance Read TimeclockCode where
readsPrec _ ('b' : xs) = [(SetBalance, xs)] readsPrec _ ('b' : xs) = [(SetBalance, xs)]
readsPrec _ ('h' : xs) = [(SetRequiredHours, xs)] readsPrec _ ('h' : xs) = [(SetRequiredHours, xs)]
readsPrec _ ('i' : xs) = [(In, xs)] readsPrec _ ('i' : xs) = [(In, xs)]
@ -48,32 +48,32 @@ instance Read TimeLogCode where
-- | Convert time log entries to journal transactions. When there is no -- | Convert time log entries to journal transactions. When there is no
-- clockout, add one with the provided current time. Sessions crossing -- clockout, add one with the provided current time. Sessions crossing
-- midnight are split into days to give accurate per-day totals. -- midnight are split into days to give accurate per-day totals.
timeLogEntriesToTransactions :: LocalTime -> [TimeLogEntry] -> [Transaction] timeclockEntriesToTransactions :: LocalTime -> [TimeclockEntry] -> [Transaction]
timeLogEntriesToTransactions _ [] = [] timeclockEntriesToTransactions _ [] = []
timeLogEntriesToTransactions now [i] timeclockEntriesToTransactions now [i]
| odate > idate = entryFromTimeLogInOut i o' : timeLogEntriesToTransactions now [i',o] | odate > idate = entryFromTimeclockInOut i o' : timeclockEntriesToTransactions now [i',o]
| otherwise = [entryFromTimeLogInOut i o] | otherwise = [entryFromTimeclockInOut i o]
where where
o = TimeLogEntry (tlsourcepos i) Out end "" "" o = TimeclockEntry (tlsourcepos i) Out end "" ""
end = if itime > now then itime else now end = if itime > now then itime else now
(itime,otime) = (tldatetime i,tldatetime o) (itime,otime) = (tldatetime i,tldatetime o)
(idate,odate) = (localDay itime,localDay otime) (idate,odate) = (localDay itime,localDay otime)
o' = o{tldatetime=itime{localDay=idate, localTimeOfDay=TimeOfDay 23 59 59}} o' = o{tldatetime=itime{localDay=idate, localTimeOfDay=TimeOfDay 23 59 59}}
i' = i{tldatetime=itime{localDay=addDays 1 idate, localTimeOfDay=midnight}} i' = i{tldatetime=itime{localDay=addDays 1 idate, localTimeOfDay=midnight}}
timeLogEntriesToTransactions now (i:o:rest) timeclockEntriesToTransactions now (i:o:rest)
| odate > idate = entryFromTimeLogInOut i o' : timeLogEntriesToTransactions now (i':o:rest) | odate > idate = entryFromTimeclockInOut i o' : timeclockEntriesToTransactions now (i':o:rest)
| otherwise = entryFromTimeLogInOut i o : timeLogEntriesToTransactions now rest | otherwise = entryFromTimeclockInOut i o : timeclockEntriesToTransactions now rest
where where
(itime,otime) = (tldatetime i,tldatetime o) (itime,otime) = (tldatetime i,tldatetime o)
(idate,odate) = (localDay itime,localDay otime) (idate,odate) = (localDay itime,localDay otime)
o' = o{tldatetime=itime{localDay=idate, localTimeOfDay=TimeOfDay 23 59 59}} o' = o{tldatetime=itime{localDay=idate, localTimeOfDay=TimeOfDay 23 59 59}}
i' = i{tldatetime=itime{localDay=addDays 1 idate, localTimeOfDay=midnight}} i' = i{tldatetime=itime{localDay=addDays 1 idate, localTimeOfDay=midnight}}
-- | Convert a timelog clockin and clockout entry to an equivalent journal -- | Convert a timeclock clockin and clockout entry to an equivalent journal
-- transaction, representing the time expenditure. Note this entry is not balanced, -- transaction, representing the time expenditure. Note this entry is not balanced,
-- since we omit the \"assets:time\" transaction for simpler output. -- since we omit the \"assets:time\" transaction for simpler output.
entryFromTimeLogInOut :: TimeLogEntry -> TimeLogEntry -> Transaction entryFromTimeclockInOut :: TimeclockEntry -> TimeclockEntry -> Transaction
entryFromTimeLogInOut i o entryFromTimeclockInOut i o
| otime >= itime = t | otime >= itime = t
| otherwise = | otherwise =
error' $ "clock-out time less than clock-in time in:\n" ++ showTransaction t error' $ "clock-out time less than clock-in time in:\n" ++ showTransaction t
@ -105,16 +105,16 @@ entryFromTimeLogInOut i o
ps = [posting{paccount=acctname, pamount=amount, ptype=VirtualPosting, ptransaction=Just t}] ps = [posting{paccount=acctname, pamount=amount, ptype=VirtualPosting, ptransaction=Just t}]
tests_Hledger_Data_TimeLog = TestList [ tests_Hledger_Data_Timeclock = TestList [
"timeLogEntriesToTransactions" ~: do "timeclockEntriesToTransactions" ~: do
today <- getCurrentDay today <- getCurrentDay
now' <- getCurrentTime now' <- getCurrentTime
tz <- getCurrentTimeZone tz <- getCurrentTimeZone
let now = utcToLocalTime tz now' let now = utcToLocalTime tz now'
nowstr = showtime now nowstr = showtime now
yesterday = prevday today yesterday = prevday today
clockin = TimeLogEntry nullsourcepos In clockin = TimeclockEntry nullsourcepos In
mktime d = LocalTime d . fromMaybe midnight . mktime d = LocalTime d . fromMaybe midnight .
#if MIN_VERSION_time(1,5,0) #if MIN_VERSION_time(1,5,0)
parseTimeM True defaultTimeLocale "%H:%M:%S" parseTimeM True defaultTimeLocale "%H:%M:%S"
@ -122,7 +122,7 @@ tests_Hledger_Data_TimeLog = TestList [
parseTime defaultTimeLocale "%H:%M:%S" parseTime defaultTimeLocale "%H:%M:%S"
#endif #endif
showtime = formatTime defaultTimeLocale "%H:%M" showtime = formatTime defaultTimeLocale "%H:%M"
assertEntriesGiveStrings name es ss = assertEqual name ss (map tdescription $ timeLogEntriesToTransactions now es) assertEntriesGiveStrings name es ss = assertEqual name ss (map tdescription $ timeclockEntriesToTransactions now es)
assertEntriesGiveStrings "started yesterday, split session at midnight" assertEntriesGiveStrings "started yesterday, split session at midnight"
[clockin (mktime yesterday "23:00:00") "" ""] [clockin (mktime yesterday "23:00:00") "" ""]

View File

@ -199,19 +199,19 @@ data PeriodicTransaction = PeriodicTransaction {
instance NFData PeriodicTransaction instance NFData PeriodicTransaction
data TimeLogCode = SetBalance | SetRequiredHours | In | Out | FinalOut deriving (Eq,Ord,Typeable,Data,Generic) data TimeclockCode = SetBalance | SetRequiredHours | In | Out | FinalOut deriving (Eq,Ord,Typeable,Data,Generic)
instance NFData TimeLogCode instance NFData TimeclockCode
data TimeLogEntry = TimeLogEntry { data TimeclockEntry = TimeclockEntry {
tlsourcepos :: GenericSourcePos, tlsourcepos :: GenericSourcePos,
tlcode :: TimeLogCode, tlcode :: TimeclockCode,
tldatetime :: LocalTime, tldatetime :: LocalTime,
tlaccount :: String, tlaccount :: String,
tldescription :: String tldescription :: String
} deriving (Eq,Ord,Typeable,Data,Generic) } deriving (Eq,Ord,Typeable,Data,Generic)
instance NFData TimeLogEntry instance NFData TimeclockEntry
data MarketPrice = MarketPrice { data MarketPrice = MarketPrice {
mpdate :: Day, mpdate :: Day,
@ -250,7 +250,7 @@ data Journal = Journal {
jmodifiertxns :: [ModifierTransaction], jmodifiertxns :: [ModifierTransaction],
jperiodictxns :: [PeriodicTransaction], jperiodictxns :: [PeriodicTransaction],
jtxns :: [Transaction], jtxns :: [Transaction],
open_timelog_entries :: [TimeLogEntry], open_timeclock_entries :: [TimeclockEntry],
jmarketprices :: [MarketPrice], jmarketprices :: [MarketPrice],
final_comment_lines :: String, -- ^ any trailing comments from the journal file final_comment_lines :: String, -- ^ any trailing comments from the journal file
jContext :: JournalContext, -- ^ the context (parse state) at the end of parsing jContext :: JournalContext, -- ^ the context (parse state) at the end of parsing

View File

@ -41,8 +41,8 @@ import Hledger.Data.Types
import Hledger.Data.Journal (nullctx) import Hledger.Data.Journal (nullctx)
import Hledger.Read.Util import Hledger.Read.Util
import Hledger.Read.JournalReader as JournalReader import Hledger.Read.JournalReader as JournalReader
import Hledger.Read.TimeclockReader as TimeclockReader
import Hledger.Read.TimedotReader as TimedotReader import Hledger.Read.TimedotReader as TimedotReader
import Hledger.Read.TimelogReader as TimelogReader
import Hledger.Read.CsvReader as CsvReader import Hledger.Read.CsvReader as CsvReader
import Hledger.Utils import Hledger.Utils
import Prelude hiding (getContents, writeFile) import Prelude hiding (getContents, writeFile)
@ -52,8 +52,8 @@ tests_Hledger_Read = TestList $
tests_readJournal' tests_readJournal'
++ [ ++ [
tests_Hledger_Read_JournalReader, tests_Hledger_Read_JournalReader,
tests_Hledger_Read_TimeclockReader,
tests_Hledger_Read_TimedotReader, tests_Hledger_Read_TimedotReader,
tests_Hledger_Read_TimelogReader,
tests_Hledger_Read_CsvReader, tests_Hledger_Read_CsvReader,
"journal" ~: do "journal" ~: do

View File

@ -1,6 +1,6 @@
{-| {-|
A reader for the timelog file format generated by timeclock.el A reader for the timeclock file format generated by timeclock.el
(<http://www.emacswiki.org/emacs/TimeClock>). Example: (<http://www.emacswiki.org/emacs/TimeClock>). Example:
@ @
@ -11,7 +11,7 @@ o 2007\/03\/10 17:26:02
From timeclock.el 2.6: From timeclock.el 2.6:
@ @
A timelog contains data in the form of a single entry per line. A timeclock contains data in the form of a single entry per line.
Each entry has the form: Each entry has the form:
CODE YYYY/MM/DD HH:MM:SS [COMMENT] CODE YYYY/MM/DD HH:MM:SS [COMMENT]
@ -40,11 +40,11 @@ i, o or O. The meanings of the codes are:
-} -}
module Hledger.Read.TimelogReader ( module Hledger.Read.TimeclockReader (
-- * Reader -- * Reader
reader, reader,
-- * Tests -- * Tests
tests_Hledger_Read_TimelogReader tests_Hledger_Read_TimeclockReader
) )
where where
import Prelude () import Prelude ()
@ -70,47 +70,47 @@ reader :: Reader
reader = Reader format detect parse reader = Reader format detect parse
format :: String format :: String
format = "timelog" format = "timeclock"
-- | Does the given file path and data look like it might be timeclock.el's timelog format ? -- | Does the given file path and data look like it might be timeclock.el's timeclock format ?
detect :: FilePath -> String -> Bool detect :: FilePath -> String -> Bool
detect f s detect f s
| f /= "-" = takeExtension f == '.':format -- from a known file name: yes if the extension is this format's name | 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 " | otherwise = regexMatches "(^|\n)[io] " s -- from stdin: yes if any line starts with "i " or "o "
-- | Parse and post-process a "Journal" from timeclock.el's timelog -- | Parse and post-process a "Journal" from timeclock.el's timeclock
-- format, saving the provided file path and the current time, or give an -- format, saving the provided file path and the current time, or give an
-- error. -- error.
parse :: Maybe FilePath -> Bool -> FilePath -> String -> ExceptT String IO Journal parse :: Maybe FilePath -> Bool -> FilePath -> String -> ExceptT String IO Journal
parse _ = parseAndFinaliseJournal timelogfilep parse _ = parseAndFinaliseJournal timeclockfilep
timelogfilep :: ParsecT [Char] JournalContext (ExceptT String IO) (JournalUpdate, JournalContext) timeclockfilep :: ParsecT [Char] JournalContext (ExceptT String IO) (JournalUpdate, JournalContext)
timelogfilep = do items <- many timelogitemp timeclockfilep = do items <- many timeclockitemp
eof eof
ctx <- getState ctx <- getState
return (liftM (foldl' (\acc new x -> new (acc x)) id) $ sequence items, ctx) return (liftM (foldl' (\acc new x -> new (acc x)) id) $ sequence items, ctx)
where where
-- As all ledger line types can be distinguished by the first -- As all ledger line types can be distinguished by the first
-- character, excepting transactions versus empty (blank or -- character, excepting transactions versus empty (blank or
-- comment-only) lines, can use choice w/o try -- comment-only) lines, can use choice w/o try
timelogitemp = choice [ directivep timeclockitemp = choice [ directivep
, liftM (return . addMarketPrice) marketpricedirectivep , liftM (return . addMarketPrice) marketpricedirectivep
, defaultyeardirectivep , defaultyeardirectivep
, emptyorcommentlinep >> return (return id) , emptyorcommentlinep >> return (return id)
, liftM (return . addTimeLogEntry) timelogentryp , liftM (return . addTimeclockEntry) timeclockentryp
] <?> "timelog entry, or default year or historical price directive" ] <?> "timeclock entry, or default year or historical price directive"
-- | Parse a timelog entry. -- | Parse a timeclock entry.
timelogentryp :: ParsecT [Char] JournalContext (ExceptT String IO) TimeLogEntry timeclockentryp :: ParsecT [Char] JournalContext (ExceptT String IO) TimeclockEntry
timelogentryp = do timeclockentryp = do
sourcepos <- genericSourcePos <$> getPosition sourcepos <- genericSourcePos <$> getPosition
code <- oneOf "bhioO" code <- oneOf "bhioO"
many1 spacenonewline many1 spacenonewline
datetime <- datetimep datetime <- datetimep
account <- fromMaybe "" <$> optionMaybe (many1 spacenonewline >> modifiedaccountnamep) account <- fromMaybe "" <$> optionMaybe (many1 spacenonewline >> modifiedaccountnamep)
description <- fromMaybe "" <$> optionMaybe (many1 spacenonewline >> restofline) description <- fromMaybe "" <$> optionMaybe (many1 spacenonewline >> restofline)
return $ TimeLogEntry sourcepos (read [code]) datetime account description return $ TimeclockEntry sourcepos (read [code]) datetime account description
tests_Hledger_Read_TimelogReader = TestList [ tests_Hledger_Read_TimeclockReader = TestList [
] ]

View File

@ -21,7 +21,7 @@ import Hledger.Data.Journal () -- Show instance
import Hledger.Data.Types import Hledger.Data.Types
import Hledger.Read.JournalReader as JournalReader import Hledger.Read.JournalReader as JournalReader
import Hledger.Read.TimedotReader as TimedotReader import Hledger.Read.TimedotReader as TimedotReader
import Hledger.Read.TimelogReader as TimelogReader import Hledger.Read.TimeclockReader as TimeclockReader
import Hledger.Read.CsvReader as CsvReader import Hledger.Read.CsvReader as CsvReader
import Hledger.Utils import Hledger.Utils
import Prelude hiding (getContents, writeFile) import Prelude hiding (getContents, writeFile)
@ -37,7 +37,7 @@ journalDefaultFilename = ".hledger.journal"
readers :: [Reader] readers :: [Reader]
readers = [ readers = [
JournalReader.reader JournalReader.reader
,TimelogReader.reader ,TimeclockReader.reader
,TimedotReader.reader ,TimedotReader.reader
,CsvReader.reader ,CsvReader.reader
] ]

View File

@ -232,7 +232,7 @@ Released under GNU GPL v3 or later.
.SH SEE ALSO .SH SEE ALSO
hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1), hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1),
hledger_csv(5), hledger_journal(5), hledger_timelog(5), hledger_timedot(5), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_timedot(5),
ledger(1) ledger(1)
http://hledger.org http://hledger.org

View File

@ -805,7 +805,7 @@ Glob patterns (\f[C]*\f[]) are not currently supported.
.PP .PP
The \f[C]include\f[] directive may only be used in journal files, and The \f[C]include\f[] directive may only be used in journal files, and
currently it may only include other journal files (eg, not CSV or currently it may only include other journal files (eg, not CSV or
timelog files.) timeclock files.)
.SH EDITOR SUPPORT .SH EDITOR SUPPORT
.PP .PP
Add\-on modes exist for various text editors, to make working with Add\-on modes exist for various text editors, to make working with
@ -863,7 +863,7 @@ Released under GNU GPL v3 or later.
.SH SEE ALSO .SH SEE ALSO
hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1), hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1),
hledger_csv(5), hledger_journal(5), hledger_timelog(5), hledger_timedot(5), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_timedot(5),
ledger(1) ledger(1)
http://hledger.org http://hledger.org

View File

@ -691,7 +691,7 @@ If the path does not begin with a slash, it is relative to the current file.
Glob patterns (`*`) are not currently supported. Glob patterns (`*`) are not currently supported.
The `include` directive may only be used in journal files, and currently The `include` directive may only be used in journal files, and currently
it may only include other journal files (eg, not CSV or timelog files.) it may only include other journal files (eg, not CSV or timeclock files.)
# EDITOR SUPPORT # EDITOR SUPPORT

View File

@ -1,14 +1,14 @@
.TH "hledger_timelog" "5" "April 2016" "" "hledger User Manuals" .TH "hledger_timeclock" "5" "April 2016" "" "hledger User Manuals"
.SH NAME .SH NAME
.PP .PP
Timelog \- the timeclock time logging format, as read by hledger Timeclock \- the time logging format of timeclock.el, as read by hledger
.SH DESCRIPTION .SH DESCRIPTION
.PP .PP
hledger can read timelog files. hledger can read timeclock files.
As with Ledger, these are (a subset of) timeclock.el\[aq]s format, As with Ledger, these are (a subset of) timeclock.el\[aq]s format,
containing clock\-in and clock\-out entries as in the example below. containing clock\-in and clock\-out entries as in the example below.
The date is a simple date (also, default year directives work). The date is a simple date (also, default year directives work).
@ -35,7 +35,7 @@ entries:
.IP .IP
.nf .nf
\f[C] \f[C]
$\ hledger\ \-f\ t.timelog\ print $\ hledger\ \-f\ t.timeclock\ print
2015/03/30\ *\ optional\ description\ after\ two\ spaces 2015/03/30\ *\ optional\ description\ after\ two\ spaces
\ \ \ \ (some:account\ name)\ \ \ \ \ \ \ \ \ 0.33h \ \ \ \ (some:account\ name)\ \ \ \ \ \ \ \ \ 0.33h
@ -47,13 +47,13 @@ $\ hledger\ \-f\ t.timelog\ print
\f[] \f[]
.fi .fi
.PP .PP
Here is a sample.timelog to download and some queries to try: Here is a sample.timeclock to download and some queries to try:
.IP .IP
.nf .nf
\f[C] \f[C]
$\ hledger\ \-f\ sample.timelog\ balance\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ #\ current\ time\ balances $\ hledger\ \-f\ sample.timeclock\ balance\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ #\ current\ time\ balances
$\ hledger\ \-f\ sample.timelog\ register\ \-p\ 2009/3\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ #\ sessions\ in\ march\ 2009 $\ hledger\ \-f\ sample.timeclock\ register\ \-p\ 2009/3\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ #\ sessions\ in\ march\ 2009
$\ hledger\ \-f\ sample.timelog\ register\ \-p\ weekly\ \-\-depth\ 1\ \-\-empty\ \ #\ time\ summary\ by\ week $\ hledger\ \-f\ sample.timeclock\ register\ \-p\ weekly\ \-\-depth\ 1\ \-\-empty\ \ #\ time\ summary\ by\ week
\f[] \f[]
.fi .fi
.PP .PP
@ -94,7 +94,7 @@ Released under GNU GPL v3 or later.
.SH SEE ALSO .SH SEE ALSO
hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1), hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1),
hledger_csv(5), hledger_journal(5), hledger_timelog(5), hledger_timedot(5), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_timedot(5),
ledger(1) ledger(1)
http://hledger.org http://hledger.org

View File

@ -1,4 +1,4 @@
% hledger_timelog(5) % hledger_timeclock(5)
% %
% April 2016 % April 2016
@ -9,13 +9,13 @@
# NAME # NAME
Timelog - the timeclock time logging format, as read by hledger Timeclock - the time logging format of timeclock.el, as read by hledger
# DESCRIPTION # DESCRIPTION
</div> </div>
hledger can read timelog files. hledger can read 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,
@ -25,7 +25,7 @@ The time format is HH:MM[:SS][+-ZZZZ]. Seconds and timezone are optional.
The timezone, if present, must be four digits and is ignored The timezone, if present, must be four digits and is ignored
(currently the time is always interpreted as a local time). (currently the time is always interpreted as a local time).
```timelog ```timeclock
i 2015/03/30 09:00:00 some:account name optional description after two spaces i 2015/03/30 09:00:00 some:account name optional description after two spaces
o 2015/03/30 09:20:00 o 2015/03/30 09:20:00
i 2015/03/31 22:21:45 another account i 2015/03/31 22:21:45 another account
@ -38,7 +38,7 @@ one day, it is split into several transactions, one for each day. For
the above time log, `hledger print` generates these journal entries: the above time log, `hledger print` generates these journal entries:
``` {.shell} ``` {.shell}
$ hledger -f t.timelog print $ hledger -f t.timeclock print
2015/03/30 * optional description after two spaces 2015/03/30 * optional description after two spaces
(some:account name) 0.33h (some:account name) 0.33h
@ -51,13 +51,13 @@ $ hledger -f t.timelog print
``` ```
Here is a Here is a
[sample.timelog](https://raw.github.com/simonmichael/hledger/master/data/sample.timelog) to [sample.timeclock](https://raw.github.com/simonmichael/hledger/master/data/sample.timeclock) to
download and some queries to try: download and some queries to try:
```shell ```shell
$ hledger -f sample.timelog balance # current time balances $ hledger -f sample.timeclock balance # current time balances
$ hledger -f sample.timelog register -p 2009/3 # sessions in march 2009 $ hledger -f sample.timeclock register -p 2009/3 # sessions in march 2009
$ hledger -f sample.timelog register -p weekly --depth 1 --empty # time summary by week $ hledger -f sample.timeclock register -p weekly --depth 1 --empty # time summary by week
``` ```
To generate time logs, ie to clock in and clock out, you could: To generate time logs, ie to clock in and clock out, you could:

View File

@ -20,7 +20,7 @@ Though called "timedot", the format does not specify the commodity being
logged, so could represent other dated, quantifiable things. logged, so could represent other dated, quantifiable things.
Eg you could record a single\-entry journal of financial transactions, Eg you could record a single\-entry journal of financial transactions,
perhaps slightly more conveniently than with hledger_journal(5) format. perhaps slightly more conveniently than with hledger_journal(5) format.
.SS Format .SH FILE FORMAT
.PP .PP
A timedot file contains a series of day entries. A timedot file contains a series of day entries.
A day entry begins with a date, and is followed by category/quantity A day entry begins with a date, and is followed by category/quantity
@ -140,7 +140,7 @@ Released under GNU GPL v3 or later.
.SH SEE ALSO .SH SEE ALSO
hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1), hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1),
hledger_csv(5), hledger_journal(5), hledger_timelog(5), hledger_timedot(5), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_timedot(5),
ledger(1) ledger(1)
http://hledger.org http://hledger.org

View File

@ -23,7 +23,7 @@ It can be formatted like a bar chart, making clear at a glance where time was sp
Though called "timedot", the format does not specify the commodity being logged, so could represent other dated, quantifiable things. 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. Eg you could record a single-entry journal of financial transactions, perhaps slightly more conveniently than with hledger_journal(5) format.
## Format # FILE FORMAT
A timedot file contains a series of day entries. 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. A day entry begins with a date, and is followed by category/quantity pairs, one per line.

View File

@ -106,7 +106,7 @@ library:
- Hledger.Data.StringFormat - Hledger.Data.StringFormat
- Hledger.Data.Posting - Hledger.Data.Posting
- Hledger.Data.RawOptions - Hledger.Data.RawOptions
- Hledger.Data.TimeLog - Hledger.Data.Timeclock
- Hledger.Data.Transaction - Hledger.Data.Transaction
- Hledger.Data.Types - Hledger.Data.Types
- Hledger.Query - Hledger.Query
@ -114,7 +114,7 @@ library:
- Hledger.Read.CsvReader - Hledger.Read.CsvReader
- Hledger.Read.JournalReader - Hledger.Read.JournalReader
- Hledger.Read.TimedotReader - Hledger.Read.TimedotReader
- Hledger.Read.TimelogReader - Hledger.Read.TimeclockReader
- Hledger.Read.Util - Hledger.Read.Util
- Hledger.Reports - Hledger.Reports
- Hledger.Reports.ReportOptions - Hledger.Reports.ReportOptions

View File

@ -31,7 +31,7 @@ extra-source-files:
doc/hledger_csv.5 doc/hledger_csv.5
doc/hledger_journal.5 doc/hledger_journal.5
doc/hledger_timedot.5 doc/hledger_timedot.5
doc/hledger_timelog.5 doc/hledger_timeclock.5
source-repository head source-repository head
type: git type: git
@ -100,7 +100,7 @@ library
Hledger.Data.StringFormat Hledger.Data.StringFormat
Hledger.Data.Posting Hledger.Data.Posting
Hledger.Data.RawOptions Hledger.Data.RawOptions
Hledger.Data.TimeLog Hledger.Data.Timeclock
Hledger.Data.Transaction Hledger.Data.Transaction
Hledger.Data.Types Hledger.Data.Types
Hledger.Query Hledger.Query
@ -108,7 +108,7 @@ library
Hledger.Read.CsvReader Hledger.Read.CsvReader
Hledger.Read.JournalReader Hledger.Read.JournalReader
Hledger.Read.TimedotReader Hledger.Read.TimedotReader
Hledger.Read.TimelogReader Hledger.Read.TimeclockReader
Hledger.Read.Util Hledger.Read.Util
Hledger.Reports Hledger.Reports
Hledger.Reports.ReportOptions Hledger.Reports.ReportOptions

View File

@ -324,7 +324,7 @@ Released under GNU GPL v3 or later.
.SH SEE ALSO .SH SEE ALSO
hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1), hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1),
hledger_csv(5), hledger_journal(5), hledger_timelog(5), hledger_timedot(5), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_timedot(5),
ledger(1) ledger(1)
http://hledger.org http://hledger.org

View File

@ -73,7 +73,7 @@ Note there is no built\-in access control, so you will need to hide
hledger\-web behind an authenticating proxy (such as apache or nginx) if hledger\-web behind an authenticating proxy (such as apache or nginx) if
you want to restrict who can see and add entries to your journal. you want to restrict who can see and add entries to your journal.
.PP .PP
With journal and timelog files (but not CSV files, currently) the web With journal and timeclock files (but not CSV files, currently) the web
app detects changes and will show the new data on the next request. app detects changes and will show the new data on the next request.
If a change makes the file unparseable, hledger\-web will show an error If a change makes the file unparseable, hledger\-web will show an error
until the file has been fixed. until the file has been fixed.
@ -249,7 +249,7 @@ Released under GNU GPL v3 or later.
.SH SEE ALSO .SH SEE ALSO
hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1), hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1),
hledger_csv(5), hledger_journal(5), hledger_timelog(5), hledger_timedot(5), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_timedot(5),
ledger(1) ledger(1)
http://hledger.org http://hledger.org

View File

@ -77,7 +77,7 @@ Note there is no built-in access control, so you will need to hide
hledger-web behind an authenticating proxy (such as apache or nginx) hledger-web behind an authenticating proxy (such as apache or nginx)
if you want to restrict who can see and add entries to your journal. if you want to restrict who can see and add entries to your journal.
With journal and timelog files (but not CSV files, currently) With journal and timeclock files (but not CSV files, currently)
the web app detects changes and will show the new data on the next request. the web app detects changes and will show the new data on the next request.
If a change makes the file unparseable, hledger-web will show an error If a change makes the file unparseable, hledger-web will show an error
until the file has been fixed. until the file has been fixed.

View File

@ -2138,7 +2138,7 @@ Released under GNU GPL v3 or later.
.SH SEE ALSO .SH SEE ALSO
hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1), hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1),
hledger_csv(5), hledger_journal(5), hledger_timelog(5), hledger_timedot(5), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_timedot(5),
ledger(1) ledger(1)
http://hledger.org http://hledger.org

2
site/.gitignore vendored
View File

@ -9,5 +9,5 @@ hledger-web.md
hledger.md hledger.md
csv.md csv.md
journal.md journal.md
timeclock.md
timedot.md timedot.md
timelog.md

View File

@ -32,7 +32,7 @@ h4, h5, h6 {
border:thin solid #cec; border:thin solid #cec;
/* border:none; */ /* border:none; */
} }
.timelog { .timeclock {
background-color:#ffe; background-color:#ffe;
border:thin solid #eec; border:thin solid #eec;
/* border:none; */ /* border:none; */

View File

@ -65,7 +65,7 @@ A JSON API server.
<!-- **[CSV](manual2.html#csv-format)** --> <!-- **[CSV](manual2.html#csv-format)** -->
<!-- **[Timeclock](manual2.html#timelog-format)** --> <!-- **[Timeclock](manual2.html#timeclock-format)** -->
<!-- **[Timedot](manual2.html#timedot-format)** --> <!-- **[Timedot](manual2.html#timedot-format)** -->
@ -75,7 +75,7 @@ A JSON API server.
#### [CSV](csv.html) #### [CSV](csv.html)
<!-- How hledger reads Comma Separated Value data. --> <!-- How hledger reads Comma Separated Value data. -->
#### [Timeclock](timelog.html) #### [Timeclock](timeclock.html)
<!-- Timeclock format, a sequence of clock-in/clock-out records. --> <!-- Timeclock format, a sequence of clock-in/clock-out records. -->
#### [Timedot](timedot.html) #### [Timedot](timedot.html)

View File

@ -77,7 +77,7 @@ hledger's primary data format, representing a general journal.
#### [hledger_csv(5)](csv.html) #### [hledger_csv(5)](csv.html)
How hledger reads Comma Separated Value data. How hledger reads Comma Separated Value data.
#### [hledger_timelog(5)](timelog.html) #### [hledger_timeclock(5)](timeclock.html)
Timeclock format, a sequence of clock-in/clock-out records. Timeclock format, a sequence of clock-in/clock-out records.
#### [hledger_timedot(5)](timedot.html) #### [hledger_timedot(5)](timedot.html)

View File

@ -78,7 +78,7 @@ We currently support:
- Ledger's journal format, mostly - Ledger's journal format, mostly
- csv format - csv format
- timelog format - timeclock format
- regular journal transactions - regular journal transactions
- multiple commodities - multiple commodities
- fixed transaction prices - fixed transaction prices
@ -135,9 +135,9 @@ or [balance assertions](manual.html#assertions-and-ordering).
- hledger shows start and end dates of the intervals requested, - hledger shows start and end dates of the intervals requested,
not just the span containing data not just the span containing data
- hledger always shows timelog balances in hours - hledger always shows timeclock balances in hours
- hledger splits multi-day timelog sessions at midnight by default (Ledger does this with an option) - hledger splits multi-day timeclock sessions at midnight by default (Ledger does this with an option)
- hledger's output follows the decimal point character, digit grouping, - hledger's output follows the decimal point character, digit grouping,
and digit group separator character used in the journal. and digit group separator character used in the journal.
@ -156,14 +156,14 @@ or [balance assertions](manual.html#assertions-and-ordering).
seen. Ledger uses D only for commodity display settings and for the seen. Ledger uses D only for commodity display settings and for the
entry command. entry command.
- hledger generates a description for timelog sessions, instead of - hledger generates a description for timeclock sessions, instead of
taking it from the clock-out entry taking it from the clock-out entry
- hledger's [include directive](manual.html#including-other-files) does not support - hledger's [include directive](manual.html#including-other-files) does not support
shell glob patterns (eg `include *.journal` ), which Ledger's does. shell glob patterns (eg `include *.journal` ), which Ledger's does.
- hledger's include directive works only in journal files, and currently can only include - hledger's include directive works only in journal files, and currently can only include
journal files, not eg timelog or CSV files journal files, not eg timeclock or CSV files
- when checking [balance assertions](manual.html#balance-assertions) - when checking [balance assertions](manual.html#balance-assertions)
hledger sorts the account's postings first by date and then (for hledger sorts the account's postings first by date and then (for

View File

@ -1,4 +1,4 @@
# a timelog session is parsed as a similarly-named transaction with one virtual posting # a timeclock session is parsed as a similarly-named transaction with one virtual posting
hledger -f - print hledger -f - print
<<< <<<
i 2009/1/1 08:00:00 i 2009/1/1 08:00:00
@ -21,9 +21,9 @@ o 2009/1/3 09:00:00
>>>2 >>>2
>>>= 0 >>>= 0
# ledger timelog example from #ledger # ledger timeclock example from #ledger
# ==== consulting.timelog # ==== consulting.timeclock
# ; Timelog for consulting sideline # ; Time log for consulting sideline
# ; All times UTC # ; All times UTC
# i 2011/01/26 16:00:00 XXXX:Remote "IPMI Access" # i 2011/01/26 16:00:00 XXXX:Remote "IPMI Access"
# o 2011/01/26 16:15:00 # o 2011/01/26 16:15:00
@ -39,7 +39,7 @@ o 2009/1/3 09:00:00
# ; Ledger for Consulting sideline # ; Ledger for Consulting sideline
# !account Consulting # !account Consulting
# !include consulting.timelog # !include consulting.timeclock
# !end # !end

2
tools/.gitignore vendored
View File

@ -1 +1 @@
generatetimelog generatetimeclock

View File

@ -1,8 +1,8 @@
#!/usr/bin/env runhaskell #!/usr/bin/env runhaskell
{- {-
generatetimelog.hs NUMENTRIES generatetimeclock.hs NUMENTRIES
Outputs a dummy timelog with the specified number of clock-in/clock-out entries, Outputs a dummy timeclock log with the specified number of clock-in/clock-out entries,
one per day. one per day.
-} -}