From 93c1328b171e0afb3911f45815139b1fed682ea9 Mon Sep 17 00:00:00 2001 From: Bodigrim <andrew.lelechenko@gmail.com> Date: Thu, 6 May 2021 19:12:57 +0100 Subject: [PATCH] Fix build warnings --- benchmarks/haskell/Benchmarks/Builder.hs | 4 +++- benchmarks/haskell/Benchmarks/DecodeUtf8.hs | 1 + benchmarks/haskell/Benchmarks/FileRead.hs | 5 ++++ .../haskell/Benchmarks/Programs/BigTable.hs | 6 +++-- .../haskell/Benchmarks/Programs/Fold.hs | 4 +++- .../haskell/Benchmarks/Programs/Sort.hs | 4 +++- benchmarks/haskell/Benchmarks/Pure.hs | 2 ++ .../Text/Internal/Lazy/Encoding/Fusion.hs | 1 - tests/Tests/Properties/Builder.hs | 4 +++- tests/Tests/Properties/Instances.hs | 3 +++ tests/Tests/Properties/LowLevel.hs | 23 ++++++++----------- tests/Tests/Properties/Transcoding.hs | 2 +- tests/Tests/QuickCheckUtils.hs | 2 ++ 13 files changed, 40 insertions(+), 21 deletions(-) diff --git a/benchmarks/haskell/Benchmarks/Builder.hs b/benchmarks/haskell/Benchmarks/Builder.hs index 8373dab7..bcc9108b 100644 --- a/benchmarks/haskell/Benchmarks/Builder.hs +++ b/benchmarks/haskell/Benchmarks/Builder.hs @@ -4,7 +4,7 @@ -- -- * Concatenating many small strings using a builder -- -{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE CPP, OverloadedStrings #-} module Benchmarks.Builder ( benchmark ) where @@ -12,7 +12,9 @@ module Benchmarks.Builder import Test.Tasty.Bench (Benchmark, bgroup, bench, nf) import Data.Binary.Builder as B import Data.ByteString.Char8 () +#if !MIN_VERSION_base(4,8,0) import Data.Monoid (mconcat, mempty) +#endif import qualified Data.ByteString.Builder as Blaze import qualified Data.ByteString as SB import qualified Data.ByteString.Lazy as LB diff --git a/benchmarks/haskell/Benchmarks/DecodeUtf8.hs b/benchmarks/haskell/Benchmarks/DecodeUtf8.hs index 22418c6c..0cf846de 100644 --- a/benchmarks/haskell/Benchmarks/DecodeUtf8.hs +++ b/benchmarks/haskell/Benchmarks/DecodeUtf8.hs @@ -1,4 +1,5 @@ {-# LANGUAGE ForeignFunctionInterface #-} +{-# OPTIONS_GHC -fno-warn-deprecations #-} -- | Test decoding of UTF-8 -- diff --git a/benchmarks/haskell/Benchmarks/FileRead.hs b/benchmarks/haskell/Benchmarks/FileRead.hs index 2b7bfcec..01b3709d 100644 --- a/benchmarks/haskell/Benchmarks/FileRead.hs +++ b/benchmarks/haskell/Benchmarks/FileRead.hs @@ -4,11 +4,16 @@ -- -- * Reading a file from the disk -- + +{-# LANGUAGE CPP #-} + module Benchmarks.FileRead ( benchmark ) where +#if !MIN_VERSION_base(4,8,0) import Control.Applicative ((<$>)) +#endif import Test.Tasty.Bench (Benchmark, bgroup, bench, whnfIO) import qualified Data.ByteString as SB import qualified Data.ByteString.Lazy as LB diff --git a/benchmarks/haskell/Benchmarks/Programs/BigTable.hs b/benchmarks/haskell/Benchmarks/Programs/BigTable.hs index e5b69481..fa56e0f8 100644 --- a/benchmarks/haskell/Benchmarks/Programs/BigTable.hs +++ b/benchmarks/haskell/Benchmarks/Programs/BigTable.hs @@ -6,13 +6,15 @@ -- -- * Writing to a handle -- -{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE CPP, OverloadedStrings #-} module Benchmarks.Programs.BigTable ( benchmark ) where import Test.Tasty.Bench (Benchmark, bench, whnfIO) -import Data.Monoid (mappend, mconcat) +#if !MIN_VERSION_base(4,8,0) +import Data.Monoid (mconcat, mempty) +#endif import Data.Text.Lazy.Builder (Builder, fromText, toLazyText) import Data.Text.Lazy.IO (hPutStr) import System.IO (Handle) diff --git a/benchmarks/haskell/Benchmarks/Programs/Fold.hs b/benchmarks/haskell/Benchmarks/Programs/Fold.hs index 8b0d2685..6be8e73b 100644 --- a/benchmarks/haskell/Benchmarks/Programs/Fold.hs +++ b/benchmarks/haskell/Benchmarks/Programs/Fold.hs @@ -12,14 +12,16 @@ -- -- * Writing back to a handle -- -{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE CPP, OverloadedStrings #-} module Benchmarks.Programs.Fold ( benchmark ) where import Data.List (foldl') import Data.List (intersperse) +#if !MIN_VERSION_base(4,8,0) import Data.Monoid (mempty, mappend, mconcat) +#endif import System.IO (Handle) import Test.Tasty.Bench (Benchmark, bench, whnfIO) import qualified Data.Text as T diff --git a/benchmarks/haskell/Benchmarks/Programs/Sort.hs b/benchmarks/haskell/Benchmarks/Programs/Sort.hs index 7379212f..7361f8e0 100644 --- a/benchmarks/haskell/Benchmarks/Programs/Sort.hs +++ b/benchmarks/haskell/Benchmarks/Programs/Sort.hs @@ -12,13 +12,15 @@ -- -- * Writing back to a handle -- -{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE CPP, OverloadedStrings #-} module Benchmarks.Programs.Sort ( benchmark ) where import Test.Tasty.Bench (Benchmark, bgroup, bench, whnfIO) +#if !MIN_VERSION_base(4,8,0) import Data.Monoid (mconcat) +#endif import System.IO (Handle) import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as BL diff --git a/benchmarks/haskell/Benchmarks/Pure.hs b/benchmarks/haskell/Benchmarks/Pure.hs index ed5eac7b..65c28f43 100644 --- a/benchmarks/haskell/Benchmarks/Pure.hs +++ b/benchmarks/haskell/Benchmarks/Pure.hs @@ -15,7 +15,9 @@ module Benchmarks.Pure import Control.DeepSeq (NFData (..)) import Control.Exception (evaluate) import Test.Tasty.Bench (Benchmark, bgroup, bench, nf) +#if !MIN_VERSION_base(4,8,0) import Data.Monoid (mappend, mempty) +#endif import GHC.Base (Char (..), Int (..), chr#, ord#, (+#)) import GHC.Generics (Generic) import GHC.Int (Int64) diff --git a/src/Data/Text/Internal/Lazy/Encoding/Fusion.hs b/src/Data/Text/Internal/Lazy/Encoding/Fusion.hs index 43dabd9b..c60ad4e4 100644 --- a/src/Data/Text/Internal/Lazy/Encoding/Fusion.hs +++ b/src/Data/Text/Internal/Lazy/Encoding/Fusion.hs @@ -54,7 +54,6 @@ import Data.ByteString.Internal (mallocByteString, memcpy) #if defined(ASSERTS) import Control.Exception (assert) #endif -import Data.Text.Internal.ByteStringCompat data S = S0 | S1 {-# UNPACK #-} !Word8 diff --git a/tests/Tests/Properties/Builder.hs b/tests/Tests/Properties/Builder.hs index 352fcad6..0f672bff 100644 --- a/tests/Tests/Properties/Builder.hs +++ b/tests/Tests/Properties/Builder.hs @@ -7,9 +7,11 @@ module Tests.Properties.Builder ( testBuilder ) where +#if !MIN_VERSION_base(4,8,0) import Data.Monoid (Monoid(..)) +#endif import Data.Int (Int8, Int16, Int32, Int64) -import Data.Word (Word, Word8, Word16, Word32, Word64) +import Data.Word import Numeric (showEFloat, showFFloat, showGFloat, showHex) import Test.QuickCheck import Test.Tasty (TestTree, testGroup) diff --git a/tests/Tests/Properties/Instances.hs b/tests/Tests/Properties/Instances.hs index c916937d..fd96ca6a 100644 --- a/tests/Tests/Properties/Instances.hs +++ b/tests/Tests/Properties/Instances.hs @@ -1,11 +1,14 @@ -- | Test instances +{-# LANGUAGE CPP #-} {-# OPTIONS_GHC -fno-enable-rewrite-rules -fno-warn-missing-signatures #-} module Tests.Properties.Instances ( testInstances ) where +#if !MIN_VERSION_base(4,8,0) import Data.Monoid (Monoid(..)) +#endif import Data.String (IsString(fromString)) import Test.QuickCheck import Test.Tasty (TestTree, testGroup) diff --git a/tests/Tests/Properties/LowLevel.hs b/tests/Tests/Properties/LowLevel.hs index 6f52ea39..4030539d 100644 --- a/tests/Tests/Properties/LowLevel.hs +++ b/tests/Tests/Properties/LowLevel.hs @@ -74,12 +74,12 @@ t_copy t = T.copy t === t -- Input and output. -t_put_get = write_read T.unlines T.filter put get - where put h = withRedirect h IO.stdout . T.putStr - get h = withRedirect h IO.stdin T.getContents -tl_put_get = write_read TL.unlines TL.filter put get - where put h = withRedirect h IO.stdout . TL.putStr - get h = withRedirect h IO.stdin TL.getContents +-- t_put_get = write_read T.unlines T.filter put get +-- where put h = withRedirect h IO.stdout . T.putStr +-- get h = withRedirect h IO.stdin T.getContents +-- tl_put_get = write_read TL.unlines TL.filter put get +-- where put h = withRedirect h IO.stdout . TL.putStr +-- get h = withRedirect h IO.stdin TL.getContents t_write_read = write_read T.unlines T.filter T.hPutStr T.hGetContents tl_write_read = write_read TL.unlines TL.filter TL.hPutStr TL.hGetContents @@ -113,19 +113,16 @@ testLowLevel = testProperty "t_take_drop_16" t_take_drop_16, testProperty "t_use_from" t_use_from, testProperty "t_copy" t_copy - ] + ], - {- testGroup "input-output" [ testProperty "t_write_read" t_write_read, testProperty "tl_write_read" tl_write_read, testProperty "t_write_read_line" t_write_read_line, testProperty "tl_write_read_line" tl_write_read_line - -- These tests are subject to I/O race conditions when run under - -- test-framework-quickcheck2. - -- testProperty "t_put_get" t_put_get + -- These tests are subject to I/O race conditions + -- testProperty "t_put_get" t_put_get, -- testProperty "tl_put_get" tl_put_get - ], - -} + ] ] diff --git a/tests/Tests/Properties/Transcoding.hs b/tests/Tests/Properties/Transcoding.hs index 2b612c86..33af0b0e 100644 --- a/tests/Tests/Properties/Transcoding.hs +++ b/tests/Tests/Properties/Transcoding.hs @@ -1,7 +1,7 @@ -- | Tests for encoding and decoding {-# LANGUAGE OverloadedStrings, ScopedTypeVariables #-} -{-# OPTIONS_GHC -fno-enable-rewrite-rules -fno-warn-missing-signatures -fno-warn-unused-imports #-} +{-# OPTIONS_GHC -fno-enable-rewrite-rules -fno-warn-missing-signatures -fno-warn-unused-imports -fno-warn-deprecations #-} module Tests.Properties.Transcoding ( testTranscoding ) where diff --git a/tests/Tests/QuickCheckUtils.hs b/tests/Tests/QuickCheckUtils.hs index 72ab0806..efe43cd1 100644 --- a/tests/Tests/QuickCheckUtils.hs +++ b/tests/Tests/QuickCheckUtils.hs @@ -35,7 +35,9 @@ module Tests.QuickCheckUtils , write_read ) where +#if !MIN_VERSION_base(4,8,0) import Control.Applicative ((<$>)) +#endif import Control.Arrow (first, (***)) import Control.DeepSeq (NFData (..), deepseq) import Control.Exception (bracket) -- GitLab