[commit: packages/haskell2010] master: Kill CPP conditionals for HUGS and old GHCs (8d5301d)

git at git.haskell.org git at git.haskell.org
Sat Sep 13 17:19:38 UTC 2014


Repository : ssh://git@git.haskell.org/haskell2010

On branch  : master
Link       : http://git.haskell.org/packages/haskell2010.git/commitdiff/8d5301d03f2bb945ef3c7d975dcff3a4d93a0adf

>---------------------------------------------------------------

commit 8d5301d03f2bb945ef3c7d975dcff3a4d93a0adf
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Sat Sep 13 18:47:54 2014 +0200

    Kill CPP conditionals for HUGS and old GHCs
    
    It would seem strange to want to use `haskell2010` with Hugs which never
    gained support for Haskell2010, so this commit removes that bitrotting
    part of Prelude.hs. This reduces the CPP clutter to the point of not
    requiring any CPP processing altogether anymore.


>---------------------------------------------------------------

8d5301d03f2bb945ef3c7d975dcff3a4d93a0adf
 Prelude.hs        | 46 +++-------------------------------------------
 haskell2010.cabal |  2 +-
 2 files changed, 4 insertions(+), 44 deletions(-)

diff --git a/Prelude.hs b/Prelude.hs
index b9b3b45..a0f0700 100644
--- a/Prelude.hs
+++ b/Prelude.hs
@@ -1,7 +1,4 @@
-{-# LANGUAGE BangPatterns, CPP, NoImplicitPrelude, PackageImports #-}
-#if __GLASGOW_HASKELL__ >= 701
-{-# LANGUAGE Trustworthy #-}
-#endif
+{-# LANGUAGE BangPatterns, NoImplicitPrelude, PackageImports, Trustworthy #-}
 
 -- |
 -- The Haskell 2010 Prelude: a standard module imported by default
@@ -27,10 +24,6 @@ module Prelude (
     -- *** Tuples
     fst, snd, curry, uncurry,
 
-#ifdef __HUGS__
-    (:),                -- Not legal Haskell 98
-#endif
-
     -- ** Basic type classes
     Eq((==), (/=)),
     Ord(compare, (<), (<=), (>=), (>), max, min),
@@ -128,7 +121,6 @@ module Prelude (
 
   ) where
 
-#ifndef __HUGS__
 import qualified "base" Control.Exception.Base as New (catch)
 import "base" Control.Monad
 import "base" System.IO
@@ -137,12 +129,8 @@ import "base" Data.List hiding ( splitAt )
 import "base" Data.Either
 import "base" Data.Maybe
 import "base" Data.Tuple
-#endif
 
-#ifdef __GLASGOW_HASKELL__
-import GHC.Base hiding ( ($!) )
--- import GHC.IO
--- import GHC.IO.Exception
+import GHC.Base
 import Text.Read
 import GHC.Enum
 import GHC.Num
@@ -150,35 +138,10 @@ import GHC.Real hiding ( gcd )
 import qualified GHC.Real ( gcd )
 import GHC.Float
 import GHC.Show
-#endif
-
-#ifdef __HUGS__
-import Hugs.Prelude
-#endif
-
-#ifndef __HUGS__
-infixr 0 $!
-#endif
 
 -- -----------------------------------------------------------------------------
 -- Miscellaneous functions
 
--- | Strict (call-by-value) application, defined in terms of 'seq'.
-($!)    :: (a -> b) -> a -> b
-#ifdef __GLASGOW_HASKELL__
-f $! x  = let !vx = x in f vx  -- see #2273
-#elif !defined(__HUGS__)
-f $! x  = x `seq` f x
-#endif
-
-#ifdef __HADDOCK__
--- | The value of @'seq' a b@ is bottom if @a@ is bottom, and otherwise
--- equal to @b at .  'seq' is usually introduced to improve performance by
--- avoiding unneeded laziness.
-seq :: a -> b -> b
-seq _ y = y
-#endif
-
 -- | The 'catch' function establishes a handler that receives any
 -- 'IOError' raised in the action protected by 'catch'.
 -- An 'IOError' is caught by
@@ -202,16 +165,13 @@ seq _ y = y
 catch :: IO a -> (IOError -> IO a) -> IO a
 catch = New.catch
 
-#ifdef __GLASGOW_HASKELL__
 -- | @'gcd' x y@ is the greatest (positive) integer that divides both @x@
 -- and @y@; for example @'gcd' (-3) 6@ = @3@, @'gcd' (-3) (-6)@ = @3@,
 -- @'gcd' 0 4@ = @4 at .  @'gcd' 0 0@ raises a runtime error.
 gcd             :: (Integral a) => a -> a -> a
 gcd 0 0         =  error "Prelude.gcd: gcd 0 0 is undefined"
 gcd x y         = GHC.Real.gcd x y
-#endif
 
-#ifndef __HUGS__
 -- The GHC's version of 'splitAt' is too strict in 'n' compared to
 -- Haskell98/2010 version. Ticket #1182.
 
@@ -231,4 +191,4 @@ gcd x y         = GHC.Real.gcd x y
 -- in which @n@ may be of any integral type.
 splitAt                :: Int -> [a] -> ([a],[a])
 splitAt n xs           =  (take n xs, drop n xs)
-#endif
+
diff --git a/haskell2010.cabal b/haskell2010.cabal
index cb8d539..976c33c 100644
--- a/haskell2010.cabal
+++ b/haskell2010.cabal
@@ -34,7 +34,7 @@ Library
 
     build-depends:
         array >= 0.5 && < 0.6,
-        base  >= 4.7 && < 4.9
+        base  >= 4.8 && < 4.9
 
     -- this hack adds a dependency on ghc-prim for Haddock.  The GHC
     -- build system doesn't seem to track transitive dependencies when



More information about the ghc-commits mailing list