Skip to content
Snippets Groups Projects
Commit 1735a97e authored by Simon Marlow's avatar Simon Marlow
Browse files

[project @ 1997-12-04 16:27:18 by simonm]

Move a few instances of the Bounded class from PrelBase out into a new
module PrelBounded.

This enables the minBound value for Int to be fixed using a Literal
Literal (using litlits requires an import of CCall, which imports
PrelBase, hence the need to move this stuff outside).
parent 949cc70c
No related merge requests found
......@@ -345,10 +345,6 @@ instance Enum () where
enumFromTo () () = [()]
enumFromThenTo () () () = [()]
instance Bounded () where
minBound = ()
maxBound = ()
instance Show () where
showsPrec p () = showString "()"
showList ls = showList__ (showsPrec 0) ls
......@@ -399,10 +395,6 @@ efttCh now step done
go now | done now = []
| otherwise = C# (chr# now) : go (now +# step)
instance Bounded Char where
minBound = '\0'
maxBound = '\255'
instance Show Char where
showsPrec p '\'' = showString "'\\''"
showsPrec p c = showChar '\'' . showLitChar c . showChar '\''
......@@ -532,10 +524,6 @@ eftInt now step
go now = I# now : go (now +# step)
instance Bounded Int where
minBound = -2147483647 -- **********************
maxBound = 2147483647 -- **********************
instance Num Int where
(+) x y = plusInt x y
(-) x y = minusInt x y
......
%
% (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
%
\section[PrelBounded]{Module @PrelBounded@}
Instances of Bounded for various datatypes.
\begin{code}
{-# OPTIONS -fno-implicit-prelude #-}
module PrelBounded where
import PrelBase
import CCall -- for the dependency analyser,
-- due to the use of litlits below.
instance Bounded () where
minBound = ()
maxBound = ()
instance Bounded Char where
minBound = '\0'
maxBound = '\255'
instance Bounded Int where
minBound = ``-2147483648'' -- GHC <= 2.09 had this at -2147483647
maxBound = 2147483647
\end{code}
......@@ -69,6 +69,7 @@ import PrelNum
import PrelTup
import PrelMaybe
import PrelEither
import PrelBounded
import Monad
import Maybe
import Error ( error )
......
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