rejigger Hledger.Cli tests to have correct prefix, add Cli.Utils
This commit is contained in:
parent
028303acd7
commit
76b933641d
@ -29,7 +29,8 @@ import Hledger.Cli.DocFiles
|
||||
import Hledger.Cli.Utils
|
||||
import Hledger.Cli.Version
|
||||
|
||||
tests_Cli = tests "Cli" [
|
||||
tests_Hledger
|
||||
-- unit tests for code under Hledger.Cli (hledger-lib tests not included)
|
||||
tests_Cli = tests "Hledger.Cli" [
|
||||
tests_Cli_Utils
|
||||
,tests_Commands
|
||||
]
|
||||
]
|
||||
|
||||
@ -84,6 +84,7 @@ import Hledger.Cli.Commands.Rewrite
|
||||
import Hledger.Cli.Commands.Roi
|
||||
import Hledger.Cli.Commands.Stats
|
||||
import Hledger.Cli.Commands.Tags
|
||||
import Hledger.Cli.Utils (tests_Cli_Utils)
|
||||
|
||||
-- | The cmdargs subcommand mode (for command-line parsing)
|
||||
-- and IO action (for doing the command's work) for each builtin command.
|
||||
@ -259,12 +260,16 @@ testcmd opts _undefined = do
|
||||
-- import System.IO (hSetEncoding, stdout, stderr, utf8)
|
||||
-- hSetEncoding stdout utf8
|
||||
-- hSetEncoding stderr utf8
|
||||
e <- runEasytests args $ EasyTest.tests [tests_Hledger, tests_Commands]
|
||||
e <- runEasytests args $ EasyTest.tests [
|
||||
tests_Hledger
|
||||
,tests "Hledger.Cli" [
|
||||
tests_Cli_Utils
|
||||
,tests_Commands
|
||||
]
|
||||
]
|
||||
if e then exitFailure else exitSuccess
|
||||
|
||||
|
||||
-- unit tests of hledger command-line executable
|
||||
|
||||
tests_Commands = tests "Commands" [
|
||||
tests_Balance
|
||||
,tests_Register
|
||||
|
||||
@ -1,5 +1,5 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-# LANGUAGE NoOverloadedStrings #-} -- prevent trouble if turned on in ghci
|
||||
{-|
|
||||
|
||||
Utilities for top-level modules and ghci. See also Hledger.Read and
|
||||
@ -25,6 +25,7 @@ module Hledger.Cli.Utils
|
||||
readFileStrictly,
|
||||
pivotByOpts,
|
||||
anonymiseByOpts,
|
||||
tests_Cli_Utils,
|
||||
)
|
||||
where
|
||||
import Control.Exception as C
|
||||
@ -128,7 +129,9 @@ journalApplyValue ropts j = do
|
||||
today <- getCurrentDay
|
||||
mspecifiedenddate <- specifiedEndDate ropts
|
||||
let d = fromMaybe today mspecifiedenddate
|
||||
ps = sortOn mpdate $ jmarketprices j
|
||||
-- prices are in parse order - sort into date then parse order,
|
||||
-- reversed for quick lookup of the latest price.
|
||||
ps = reverse $ sortOn mpdate $ jmarketprices j
|
||||
convert | value_ ropts = overJournalAmounts (amountValue ps d)
|
||||
| otherwise = id
|
||||
return $ convert j
|
||||
@ -232,7 +235,7 @@ fileModificationTime f
|
||||
| otherwise = (do
|
||||
utc <- getModificationTime f
|
||||
let nom = utcTimeToPOSIXSeconds utc
|
||||
let clo = TOD (read $ takeWhile (`elem` "0123456789") $ show nom) 0 -- XXX read
|
||||
let clo = TOD (read $ takeWhile (`elem` ("0123456789"::String)) $ show nom) 0 -- XXX read
|
||||
return clo
|
||||
)
|
||||
`C.catch` \(_::C.IOException) -> getClockTime
|
||||
@ -296,3 +299,7 @@ backupNumber :: FilePath -> FilePath -> Maybe Int
|
||||
backupNumber f g = case g =~ ("^" ++ f ++ "\\.([0-9]+)$") of
|
||||
(_::FilePath, _::FilePath, _::FilePath, [ext::FilePath]) -> readMay ext
|
||||
_ -> Nothing
|
||||
|
||||
tests_Cli_Utils = tests "Utils" [
|
||||
|
||||
]
|
||||
|
||||
Loading…
Reference in New Issue
Block a user