Skip to content
Snippets Groups Projects
Commit 401283a9 authored by Herbert Valerio Riedel's avatar Herbert Valerio Riedel :man_dancing:
Browse files

Kill CPP conditionals for HUGS and old GHCs

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. The same clanup was performed in the haskell2010 package
recently.
parent 51ac61ff
Branches www-improve
No related tags found
No related merge requests found
{-# LANGUAGE BangPatterns, CPP, NoImplicitPrelude, PackageImports #-}
#if __GLASGOW_HASKELL__ >= 701
{-# LANGUAGE Trustworthy #-}
#endif
{-# LANGUAGE BangPatterns, NoImplicitPrelude, PackageImports, Trustworthy #-}
-- |
-- The Haskell 98 Prelude: a standard module imported by default
......@@ -28,10 +25,6 @@ module Prelude (
-- *** Tuples
fst, snd, curry, uncurry,
#ifdef __HUGS__
(:), -- Not legal Haskell 98
#endif
-- ** Basic type classes
Eq((==), (/=)),
Ord(compare, (<), (<=), (>=), (>), max, min),
......@@ -129,7 +122,6 @@ module Prelude (
) where
#ifndef __HUGS__
import qualified "base" Control.Exception.Base as New (catch)
import "base" Control.Monad
import "base" System.IO
......@@ -138,12 +130,10 @@ import "base" Data.OldList 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 (($), ($!), (&&), (.), (||), Bool(..), Char, Eq(..), Int,
Ord(..), Ordering(..), String, asTypeOf, const, error, flip,
id, not, otherwise, seq, undefined, until)
import Text.Read
import GHC.Enum
import GHC.Num
......@@ -151,35 +141,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@. '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
......@@ -203,16 +168,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@. @'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.
......@@ -232,4 +194,3 @@ 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
......@@ -28,17 +28,14 @@ Library
default-language: Haskell98
other-extensions:
BangPatterns
CPP
NoImplicitPrelude
PackageImports
if impl(ghc)
other-extensions:
Safe
Trustworthy
Safe
Trustworthy
build-depends:
array >= 0.5 && < 0.6,
base >= 4.7 && < 4.9,
base >= 4.8 && < 4.9,
directory >= 1.2 && < 1.3,
old-locale >= 1.0 && < 1.1,
old-time >= 1.1 && < 1.2,
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment