[commit: packages/time] ghc, master: test: remove unnecessary pragmas (a03e04c)
git at git.haskell.org
git at git.haskell.org
Fri Apr 21 16:57:45 UTC 2017
Repository : ssh://git@git.haskell.org/time
On branches: ghc,master
Link : http://git.haskell.org/packages/time.git/commitdiff/a03e04cfdec877c2a79560ed296b5009cf90aba4
>---------------------------------------------------------------
commit a03e04cfdec877c2a79560ed296b5009cf90aba4
Author: Ashley Yakeley <ashley at yakeley.org>
Date: Sat Mar 11 10:14:33 2017 -0800
test: remove unnecessary pragmas
>---------------------------------------------------------------
a03e04cfdec877c2a79560ed296b5009cf90aba4
test/CurrentTime.hs | 2 --
test/ShowDST.hs | 2 --
test/TimeZone.hs | 2 --
test/main/Main.hs | 1 -
test/main/Test/Calendar/ClipDates.hs | 2 --
test/main/Test/Calendar/Easter.hs | 2 --
test/main/Test/Format/ParseTime.hs | 10 ++++------
test/main/Test/TestUtil.hs | 1 -
test/unix/Main.hs | 1 -
test/unix/Test/Format/Format.hs | 2 --
test/unix/Test/LocalTime/TimeZone.hs | 2 --
test/unix/Test/TestUtil.hs | 1 -
time.cabal | 1 +
13 files changed, 5 insertions(+), 24 deletions(-)
diff --git a/test/CurrentTime.hs b/test/CurrentTime.hs
index 981bf83..3ea641e 100644
--- a/test/CurrentTime.hs
+++ b/test/CurrentTime.hs
@@ -1,5 +1,3 @@
-{-# OPTIONS -Wall -Werror #-}
-
module Main where
import Data.Time
diff --git a/test/ShowDST.hs b/test/ShowDST.hs
index e19f3dd..8b00014 100644
--- a/test/ShowDST.hs
+++ b/test/ShowDST.hs
@@ -1,5 +1,3 @@
-{-# OPTIONS -Wall -Werror #-}
-
module Main where
import Data.Time
diff --git a/test/TimeZone.hs b/test/TimeZone.hs
index b582f53..05e56fd 100644
--- a/test/TimeZone.hs
+++ b/test/TimeZone.hs
@@ -1,5 +1,3 @@
-{-# OPTIONS -Wall -Werror #-}
-
module Main where
import Data.Time
diff --git a/test/main/Main.hs b/test/main/Main.hs
index 2d02b4a..23621d3 100644
--- a/test/main/Main.hs
+++ b/test/main/Main.hs
@@ -1,6 +1,5 @@
module Main where
-import Foreign.C.Types
import Test.Tasty
import Test.Calendar.AddDays
import Test.Calendar.Calendars
diff --git a/test/main/Test/Calendar/ClipDates.hs b/test/main/Test/Calendar/ClipDates.hs
index 848c4db..246c437 100644
--- a/test/main/Test/Calendar/ClipDates.hs
+++ b/test/main/Test/Calendar/ClipDates.hs
@@ -1,5 +1,3 @@
-{-# Language TupleSections #-}
-
module Test.Calendar.ClipDates(clipDates) where
import Data.Time.Calendar.OrdinalDate
diff --git a/test/main/Test/Calendar/Easter.hs b/test/main/Test/Calendar/Easter.hs
index 8c7e6d4..1901835 100644
--- a/test/main/Test/Calendar/Easter.hs
+++ b/test/main/Test/Calendar/Easter.hs
@@ -1,5 +1,3 @@
-{-# OPTIONS -Wall -Werror #-}
-
module Test.Calendar.Easter(testEaster) where
import Data.Time.Calendar.Easter
diff --git a/test/main/Test/Format/ParseTime.hs b/test/main/Test/Format/ParseTime.hs
index 8be9528..340f319 100644
--- a/test/main/Test/Format/ParseTime.hs
+++ b/test/main/Test/Format/ParseTime.hs
@@ -1,6 +1,4 @@
-{-# OPTIONS -fno-warn-type-defaults -fno-warn-orphans #-}
-{-# LANGUAGE FlexibleInstances, ExistentialQuantification #-}
-
+{-# OPTIONS -fno-warn-orphans #-}
module Test.Format.ParseTime(testParseTime,test_parse_format) where
import Control.Monad
@@ -82,7 +80,7 @@ readTestsParensSpaces expected target = testGroup target
readOtherTypesTest :: TestTree
readOtherTypesTest = testGroup "read other types"
[
- readTestsParensSpaces 3 "3",
+ readTestsParensSpaces (3 :: Integer) "3",
readTestsParensSpaces "a" "\"a\""
]
@@ -244,11 +242,11 @@ instance CoArbitrary Day where
instance Arbitrary DiffTime where
arbitrary = oneof [intSecs, fracSecs] -- up to 1 leap second
where intSecs = liftM secondsToDiffTime' $ choose (0, 86400)
- fracSecs = liftM picosecondsToDiffTime' $ choose (0, 86400 * 10^12)
+ fracSecs = liftM picosecondsToDiffTime' $ choose (0, 86400 * 10^(12::Int))
secondsToDiffTime' :: Integer -> DiffTime
secondsToDiffTime' = fromInteger
picosecondsToDiffTime' :: Integer -> DiffTime
- picosecondsToDiffTime' x = fromRational (x % 10^12)
+ picosecondsToDiffTime' x = fromRational (x % 10^(12::Int))
instance CoArbitrary DiffTime where
coarbitrary t = coarbitrary (fromEnum t)
diff --git a/test/main/Test/TestUtil.hs b/test/main/Test/TestUtil.hs
index c306893..e5493f8 100644
--- a/test/main/Test/TestUtil.hs
+++ b/test/main/Test/TestUtil.hs
@@ -1,4 +1,3 @@
-{-# OPTIONS -fno-warn-overlapping-patterns #-}
module Test.TestUtil where
import Test.QuickCheck.Property
diff --git a/test/unix/Main.hs b/test/unix/Main.hs
index eac8ac0..068b4ee 100644
--- a/test/unix/Main.hs
+++ b/test/unix/Main.hs
@@ -1,6 +1,5 @@
module Main where
-import Foreign.C.Types
import Test.Tasty
import Test.Format.Format
import Test.LocalTime.TimeZone
diff --git a/test/unix/Test/Format/Format.hs b/test/unix/Test/Format/Format.hs
index 753371c..a6ea8a5 100644
--- a/test/unix/Test/Format/Format.hs
+++ b/test/unix/Test/Format/Format.hs
@@ -1,5 +1,3 @@
-{-# LANGUAGE ForeignFunctionInterface #-}
-
module Test.Format.Format(testFormat) where
import Data.Time
diff --git a/test/unix/Test/LocalTime/TimeZone.hs b/test/unix/Test/LocalTime/TimeZone.hs
index ca55b25..d6e20d6 100644
--- a/test/unix/Test/LocalTime/TimeZone.hs
+++ b/test/unix/Test/LocalTime/TimeZone.hs
@@ -1,5 +1,3 @@
-{-# OPTIONS -Wall -Werror #-}
-
module Test.LocalTime.TimeZone(testTimeZone) where
import Data.Time
diff --git a/test/unix/Test/TestUtil.hs b/test/unix/Test/TestUtil.hs
index 4a3b42d..8599c0c 100644
--- a/test/unix/Test/TestUtil.hs
+++ b/test/unix/Test/TestUtil.hs
@@ -1,4 +1,3 @@
-{-# OPTIONS -fno-warn-overlapping-patterns #-}
module Test.TestUtil where
import Test.QuickCheck.Property
diff --git a/time.cabal b/time.cabal
index a3a9bf7..ae82f16 100644
--- a/time.cabal
+++ b/time.cabal
@@ -124,6 +124,7 @@ test-suite test-main
FlexibleInstances
UndecidableInstances
ScopedTypeVariables
+ TupleSections
ghc-options: -Wall -fwarn-tabs
build-depends:
base,
More information about the ghc-commits
mailing list