Skip to content

Commit

Permalink
Fix build warnings
Browse files Browse the repository at this point in the history
  • Loading branch information
Bodigrim committed May 6, 2021
1 parent 0170e9e commit d0368b6
Show file tree
Hide file tree
Showing 13 changed files with 40 additions and 21 deletions.
4 changes: 3 additions & 1 deletion benchmarks/haskell/Benchmarks/Builder.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,15 +4,17 @@
--
-- * Concatenating many small strings using a builder
--
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP, OverloadedStrings #-}
module Benchmarks.Builder
( benchmark
) where

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
Expand Down
1 change: 1 addition & 0 deletions benchmarks/haskell/Benchmarks/DecodeUtf8.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE ForeignFunctionInterface #-}
{-# OPTIONS_GHC -fno-warn-deprecations #-}

-- | Test decoding of UTF-8
--
Expand Down
5 changes: 5 additions & 0 deletions benchmarks/haskell/Benchmarks/FileRead.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
6 changes: 4 additions & 2 deletions benchmarks/haskell/Benchmarks/Programs/BigTable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down
4 changes: 3 additions & 1 deletion benchmarks/haskell/Benchmarks/Programs/Fold.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
4 changes: 3 additions & 1 deletion benchmarks/haskell/Benchmarks/Programs/Sort.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 2 additions & 0 deletions benchmarks/haskell/Benchmarks/Pure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down
1 change: 0 additions & 1 deletion src/Data/Text/Internal/Lazy/Encoding/Fusion.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
4 changes: 3 additions & 1 deletion tests/Tests/Properties/Builder.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down
3 changes: 3 additions & 0 deletions tests/Tests/Properties/Instances.hs
Original file line number Diff line number Diff line change
@@ -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)
Expand Down
23 changes: 10 additions & 13 deletions tests/Tests/Properties/LowLevel.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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

Expand Down Expand Up @@ -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
],
-}
]
]

2 changes: 1 addition & 1 deletion tests/Tests/Properties/Transcoding.hs
Original file line number Diff line number Diff line change
@@ -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
Expand Down
2 changes: 2 additions & 0 deletions tests/Tests/QuickCheckUtils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down

0 comments on commit d0368b6

Please sign in to comment.