tests: Timeclock -> easytest

This commit is contained in:
Simon Michael 2018-09-04 11:30:48 -07:00
parent 8d1506a4a4
commit a8175d8b14
2 changed files with 38 additions and 34 deletions

View File

@ -52,8 +52,7 @@ import Hledger.Utils.Test
tests_Hledger_Data = TestList tests_Hledger_Data = TestList
[ [
tests_Hledger_Data_Timeclock tests_Hledger_Data_Transaction
,tests_Hledger_Data_Transaction
] ]
easytests_Data = tests "Data" [ easytests_Data = tests "Data" [
@ -62,4 +61,5 @@ easytests_Data = tests "Data" [
,easytests_Journal ,easytests_Journal
,easytests_Ledger ,easytests_Ledger
,easytests_Posting ,easytests_Posting
,easytests_Timeclock
] ]

View File

@ -8,8 +8,12 @@ converted to 'Transactions' and queried like a ledger.
{-# LANGUAGE CPP, OverloadedStrings #-} {-# LANGUAGE CPP, OverloadedStrings #-}
module Hledger.Data.Timeclock module Hledger.Data.Timeclock (
timeclockEntriesToTransactions
,easytests_Timeclock
)
where where
import Data.Maybe import Data.Maybe
-- import Data.Text (Text) -- import Data.Text (Text)
import qualified Data.Text as T import qualified Data.Text as T
@ -22,7 +26,7 @@ import System.Locale (defaultTimeLocale)
#endif #endif
import Text.Printf import Text.Printf
import Hledger.Utils import Hledger.Utils hiding (is)
import Hledger.Data.Types import Hledger.Data.Types
import Hledger.Data.Dates import Hledger.Data.Dates
import Hledger.Data.Amount import Hledger.Data.Amount
@ -107,38 +111,38 @@ entryFromTimeclockInOut 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_Timeclock = TestList [ -- tests
"timeclockEntriesToTransactions" ~: do is :: (Eq a, Show a, HasCallStack) => a -> a -> Test ()
today <- getCurrentDay is = flip expectEq'
now' <- getCurrentTime
tz <- getCurrentTimeZone easytests_Timeclock = tests "Timeclock" [
let now = utcToLocalTime tz now' do
nowstr = showtime now today <- io getCurrentDay
yesterday = prevday today now' <- io getCurrentTime
clockin = TimeclockEntry nullsourcepos In tz <- io getCurrentTimeZone
mktime d = LocalTime d . fromMaybe midnight . let now = utcToLocalTime tz now'
nowstr = showtime now
yesterday = prevday today
clockin = TimeclockEntry nullsourcepos In
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"
#else #else
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 (T.unpack . tdescription) $ timeclockEntriesToTransactions now es) txndescs = map (T.unpack . tdescription) . timeclockEntriesToTransactions now
future = utcToLocalTime tz $ addUTCTime 100 now'
assertEntriesGiveStrings "started yesterday, split session at midnight" futurestr = showtime future
[clockin (mktime yesterday "23:00:00") "" ""] tests "timeclockEntriesToTransactions" [
["23:00-23:59","00:00-"++nowstr] test "started yesterday, split session at midnight" $
assertEntriesGiveStrings "split multi-day sessions at each midnight" txndescs [clockin (mktime yesterday "23:00:00") "" ""] `is` ["23:00-23:59","00:00-"++nowstr]
[clockin (mktime (addDays (-2) today) "23:00:00") "" ""] ,test "split multi-day sessions at each midnight" $
["23:00-23:59","00:00-23:59","00:00-"++nowstr] txndescs [clockin (mktime (addDays (-2) today) "23:00:00") "" ""] `is `["23:00-23:59","00:00-23:59","00:00-"++nowstr]
assertEntriesGiveStrings "auto-clock-out if needed" ,test "auto-clock-out if needed" $
[clockin (mktime today "00:00:00") "" ""] txndescs [clockin (mktime today "00:00:00") "" ""] `is` ["00:00-"++nowstr]
["00:00-"++nowstr] ,test "use the clockin time for auto-clockout if it's in the future" $
let future = utcToLocalTime tz $ addUTCTime 100 now' txndescs [clockin future "" ""] `is` [printf "%s-%s" futurestr futurestr]
futurestr = showtime future ]
assertEntriesGiveStrings "use the clockin time for auto-clockout if it's in the future"
[clockin future "" ""]
[printf "%s-%s" futurestr futurestr]
] ]