Skip to content

Commit

Permalink
Don’t use ImportQualifiedPost to support GHC 8.6
Browse files Browse the repository at this point in the history
  • Loading branch information
sergv committed Dec 8, 2024
1 parent 8cec53f commit 628c229
Show file tree
Hide file tree
Showing 5 changed files with 10 additions and 15 deletions.
1 change: 1 addition & 0 deletions atomic-counter.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -95,6 +95,7 @@ common ghc-options
if impl(ghc >= 8.10)
ghc-options:
-Wno-missing-safe-haskell-mode
-Wno-prepositive-qualified-module

if impl(ghc >= 9.2)
ghc-options:
Expand Down
5 changes: 2 additions & 3 deletions bench/BenchMain.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,6 @@

{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE UnboxedTuples #-}
Expand All @@ -27,9 +26,9 @@ import Test.QuickCheck
import Test.Tasty hiding (defaultMain)
import Test.Tasty.Bench
import Test.Tasty.Patterns.Printer
import Test.Tasty.QuickCheck qualified as QC
import qualified Test.Tasty.QuickCheck as QC

import Control.Concurrent.Counter.Lifted.IO qualified as C
import qualified Control.Concurrent.Counter.Lifted.IO as C

import TestUtils

Expand Down
6 changes: 2 additions & 4 deletions src/Control/Concurrent/Counter/Lifted/IO.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,8 +9,7 @@
-- operate in the 'IO' monad.
----------------------------------------------------------------------------

{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeApplications #-}

module Control.Concurrent.Counter.Lifted.IO
( Counter
Expand Down Expand Up @@ -41,8 +40,7 @@ import GHC.Exts (RealWorld)
import GHC.IO
import GHC.ST

import Control.Concurrent.Counter.Lifted.ST qualified as Lifted

import qualified Control.Concurrent.Counter.Lifted.ST as Lifted

-- | Memory location that supports select few atomic operations.
--
Expand Down
8 changes: 3 additions & 5 deletions src/Control/Concurrent/Counter/Lifted/ST.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,9 +10,8 @@
-- same operation (terms and conditions apply).
----------------------------------------------------------------------------

{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}

module Control.Concurrent.Counter.Lifted.ST
( Counter
Expand Down Expand Up @@ -41,8 +40,7 @@ import Prelude hiding (and, or)
import GHC.Exts (Int(..), Int#, State#)
import GHC.ST

import Control.Concurrent.Counter.Unlifted qualified as Unlifted

import qualified Control.Concurrent.Counter.Unlifted as Unlifted

-- | Memory location that supports select few atomic operations.
--
Expand Down
5 changes: 2 additions & 3 deletions test/TestMain.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,6 @@
----------------------------------------------------------------------------

{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE NamedFieldPuns #-}

module TestMain (main) where
Expand All @@ -18,9 +17,9 @@ import Data.IORef
import Data.Semigroup
import Test.QuickCheck
import Test.Tasty
import Test.Tasty.QuickCheck qualified as QC
import qualified Test.Tasty.QuickCheck as QC

import Control.Concurrent.Counter.Lifted.IO qualified as C
import qualified Control.Concurrent.Counter.Lifted.IO as C

import TestUtils

Expand Down

0 comments on commit 628c229

Please sign in to comment.