[commit: packages/time] format-widths, ghc, improve-leapseconds, master, posix-perf, tasty, wip/travis: more test infrastructure (b85fefa)

git at git.haskell.org git at git.haskell.org
Fri Apr 21 16:51:41 UTC 2017


Repository : ssh://git@git.haskell.org/time

On branches: format-widths,ghc,improve-leapseconds,master,posix-perf,tasty,wip/travis
Link       : http://git.haskell.org/packages/time.git/commitdiff/b85fefa65a538c2e38bd688594c68fd0d16236db

>---------------------------------------------------------------

commit b85fefa65a538c2e38bd688594c68fd0d16236db
Author: Ashley Yakeley <ashley at semantic.org>
Date:   Thu Nov 15 00:52:10 2012 -0800

    more test infrastructure
    
    Ignore-this: 7e091ce926e7c054340ecdbc1779fb84
    
    darcs-hash:20121115085210-ac6dd-a38387a32dbb5d33ce700fc5004aa8e73475831f


>---------------------------------------------------------------

b85fefa65a538c2e38bd688594c68fd0d16236db
 Test.hs               |  6 ++++++
 Test/TestParseTime.hs | 35 -----------------------------------
 2 files changed, 6 insertions(+), 35 deletions(-)

diff --git a/Test.hs b/Test.hs
new file mode 100644
index 0000000..27e2bee
--- /dev/null
+++ b/Test.hs
@@ -0,0 +1,6 @@
+module Main where
+import Test.Framework
+import Test.Tests
+
+main :: IO ()
+main = defaultMain tests
diff --git a/Test/TestParseTime.hs b/Test/TestParseTime.hs
index 823a3c1..fa7b241 100644
--- a/Test/TestParseTime.hs
+++ b/Test/TestParseTime.hs
@@ -12,13 +12,7 @@ import Data.Time.Calendar.WeekDate
 import Data.Time.Clock.POSIX
 import System.Locale
 import Test.QuickCheck hiding (Result)
---import qualified Test.QuickCheck
 import Test.TestUtil
---import qualified Test.TestUtil
-
-
---instance RunTest Property where
---    runTest p = run p (TestOptions {no_of_tests = 10000,length_of_tests = 0,debug_tests = False})
 
 ntest :: Int
 ntest = 1000
@@ -32,9 +26,6 @@ testParseTime = testGroup "testParseTime"
     testGroup "properties" (fmap (\(n,prop) -> testProperty n prop) properties)
     ]
 
-{-
-knownFailures
--}
 yearDays :: Integer -> [Day]
 yearDays y = [(fromGregorian y 1 1) .. (fromGregorian y 12 31)]
 
@@ -83,38 +74,12 @@ parseCYY c i = return $ diff (Just (fromGregorian ((c * 100) + i) 1 1)) (parse "
 parseCYY2 :: Integer -> Integer -> IO Result
 parseCYY2 c i = return $ diff (Just (fromGregorian ((c * 100) + i) 1 1)) (parse "%C %y" ((show2 c) ++ " " ++ (show2 i)))
 
-{-
-checkAll :: RunTest p => [(String,p)] -> IO Bool
-checkAll ps = fmap and (mapM checkOne ps)
-
-trMessage :: TestResult -> String
-trMessage (TestOk s _ _) = s
-trMessage (TestExausted s i ss) = "Exhausted " ++ (show s) ++ " " ++ (show i) ++ " " ++ (show ss)
-trMessage (TestFailed ss i) = "Failed " ++ (show ss) ++ " " ++ (show i)
-trMessage (TestAborted ex) = "Aborted " ++ (show ex)
-
-trGood :: TestResult -> Bool
-trGood (TestOk _ _ _) = True
-trGood _ = False
-
-checkOne :: RunTest p => (String,p) -> IO Bool
-checkOne (n,p) =
-    do
-       putStr (rpad 65 ' ' n)
-       tr <- runTest p
-       putStrLn (trMessage tr)
-       return (trGood tr)
-  where
-    rpad n' c xs = xs ++ replicate (n' - length xs) c
--}
-
 parse :: ParseTime t => String -> String -> Maybe t
 parse f t = parseTime defaultTimeLocale f t
 
 format :: (FormatTime t) => String -> t -> String
 format f t = formatTime defaultTimeLocale f t
 
-
 instance Arbitrary Day where
     arbitrary = liftM ModifiedJulianDay $ choose (-313698, 2973483) -- 1000-01-1 to 9999-12-31
 



More information about the ghc-commits mailing list