Skip to content

Commit

Permalink
Remove CPP and re-enable fourmolu where appropriate
Browse files Browse the repository at this point in the history
  • Loading branch information
andreabedini committed Jun 25, 2024
1 parent a7b032d commit e14ce68
Show file tree
Hide file tree
Showing 19 changed files with 244 additions and 265 deletions.
1 change: 0 additions & 1 deletion Cabal-QuickCheck/src/Test/QuickCheck/GenericArbitrary.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeOperators #-}
Expand Down
1 change: 0 additions & 1 deletion Cabal-syntax/src/Distribution/Compat/Graph.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
Expand Down
3 changes: 0 additions & 3 deletions Cabal-syntax/src/Distribution/Compat/Newtype.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
Expand Down Expand Up @@ -32,7 +31,6 @@ import Data.Monoid (Endo (..), Product (..), Sum (..))
-- Another approach would be to use @TypeFamilies@ (and possibly
-- compute inner type using "GHC.Generics"), but we think @FunctionalDependencies@
-- version gives cleaner type signatures.
{- FOURMOLU_DISABLE -}
class Newtype o n | n -> o where
pack :: o -> n
default pack :: Coercible o n => o -> n
Expand All @@ -41,7 +39,6 @@ class Newtype o n | n -> o where
unpack :: n -> o
default unpack :: Coercible n o => n -> o
unpack = coerce
{- FOURMOLU_ENABLE -}

instance Newtype a (Identity a)
instance Newtype a (Sum a)
Expand Down
35 changes: 18 additions & 17 deletions Cabal-syntax/src/Distribution/Compat/Prelude.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE Trustworthy #-}
Expand Down Expand Up @@ -180,23 +179,25 @@ module Distribution.Compat.Prelude
, traceShowM
) where

-- We also could hide few partial function
{- FOURMOLU_DISABLE -}
import Prelude as BasePrelude hiding
( mapM, mapM_, sequence, any, all, head, tail, last, init
-- partial functions
, read
, foldr1, foldl1
-- As of base 4.11.0.0 Prelude exports part of Semigroup(..).
-- Hide this so we instead rely on Distribution.Compat.Semigroup.
, Semigroup(..)
, Word
-- We hide them, as we import only some members
, Traversable, traverse, sequenceA
, Foldable(..)
)
{- FOURMOLU_ENABLE -}
import Data.Foldable as BasePrelude (elem, foldl, maximum, minimum, product, sum)
import Prelude as BasePrelude hiding
( Foldable (..)
, Semigroup (..)
, Traversable
, Word
, all
, any
, head
, init
, last
, mapM
, mapM_
, read
, sequence
, sequenceA
, tail
, traverse
)

-- AMP
import Data.Foldable
Expand Down
1 change: 0 additions & 1 deletion Cabal-syntax/src/Distribution/Fields/ParseResult.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}

Expand Down
1 change: 0 additions & 1 deletion Cabal-syntax/src/Distribution/Parsec.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
Expand Down
1 change: 0 additions & 1 deletion Cabal-syntax/src/Distribution/System.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
Expand Down
1 change: 0 additions & 1 deletion Cabal-tests/tests/UnitTests/Distribution/Utils/CharSet.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
module UnitTests.Distribution.Utils.CharSet where

import Prelude hiding (Foldable(..))
Expand Down
3 changes: 0 additions & 3 deletions Cabal/src/Distribution/Compat/Async.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}

-- | 'Async', yet using 'MVar's.
Expand Down Expand Up @@ -146,13 +145,11 @@ data AsyncCancelled = AsyncCancelled
, Typeable
)

{- FOURMOLU_DISABLE -}
instance Exception AsyncCancelled where
-- wraps in SomeAsyncException
-- See https://github.com/ghc/ghc/commit/756a970eacbb6a19230ee3ba57e24999e4157b09
fromException = asyncExceptionFromException
toException = asyncExceptionToException
{- FOURMOLU_ENABLE -}

-- | Cancel an asynchronous action
--
Expand Down
1 change: 0 additions & 1 deletion Cabal/src/Distribution/Compat/ResponseFile.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}

Expand Down
1 change: 0 additions & 1 deletion Cabal/src/Distribution/Compat/Stack.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE ImplicitParams #-}
{-# LANGUAGE RankNTypes #-}

Expand Down
Loading

0 comments on commit e14ce68

Please sign in to comment.