-% -----------------------------------------------------------------------------
-% $Id: Base.lhs,v 1.6 2002/02/12 09:39:19 simonmar Exp $
-%
-% (c) The University of Glasgow, 1992-2002
-%
\section[GHC.Base]{Module @GHC.Base@}
-
The overall structure of the GHC Prelude is a bit tricky.
a) We want to avoid "orphan modules", i.e. ones with instance
Other Prelude modules are much easier with fewer complex dependencies.
-
\begin{code}
{-# OPTIONS -fno-implicit-prelude #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module : GHC.Base
+-- Copyright : (c) The University of Glasgow, 1992-2002
+-- License : see libraries/base/LICENSE
+--
+-- Maintainer : cvs-ghc@haskell.org
+-- Stability : internal
+-- Portability : non-portable (GHC extensions)
+--
+-- Basic data types and classes.
+--
+-----------------------------------------------------------------------------
#include "MachDeps.h"
)
where
-import {-# SOURCE #-} GHC.Prim
+import GHC.Prim
import {-# SOURCE #-} GHC.Err
infixr 9 .
%*********************************************************
\begin{code}
+-- |The 'Bool' type is an enumeration. It is defined with 'False'
+-- first so that the corresponding 'Enum' instance will give @'fromEnum'
+-- False@ the value zero, and @'fromEnum' True@ the value 1.
data Bool = False | True deriving (Eq, Ord)
-- Read in GHC.Read, Show in GHC.Show
-- Boolean functions
-(&&), (||) :: Bool -> Bool -> Bool
+-- | Boolean \"and\"
+(&&) :: Bool -> Bool -> Bool
True && x = x
False && _ = False
+
+-- | Boolean \"or\"
+(||) :: Bool -> Bool -> Bool
True || _ = True
False || x = x
+-- | Boolean \"not\"
not :: Bool -> Bool
not True = False
not False = True
+-- |'otherwise' is defined as the value 'True'; it helps to make
+-- guards more readable. eg.
+--
+-- > f x | x \< 0 = ...
+-- > | otherwise = ...
otherwise :: Bool
otherwise = True
\end{code}
\begin{code}
data Int = I# Int#
+-- ^A fixed-precision integer type with at least the range @[-2^29
+-- .. 2^29-1]@. The exact range for a given implementation can be
+-- determined by using 'minBound' and 'maxBound' from the 'Bounded'
+-- class.
zeroInt, oneInt, twoInt, maxInt, minInt :: Int
zeroInt = I# 0#
\begin{code}
data Unit = Unit
+#ifndef __HADDOCK__
data (:+:) a b = Inl a | Inr b
data (:*:) a b = a :*: b
+#endif
\end{code}
"x# <=# x#" forall x#. x# <=# x# = True
#-}
+{-# RULES
+"plusFloat x 0.0" forall x#. plusFloat# x# 0.0# = x#
+"plusFloat 0.0 x" forall x#. plusFloat# 0.0# x# = x#
+"minusFloat x 0.0" forall x#. minusFloat# x# 0.0# = x#
+"minusFloat x x" forall x#. minusFloat# x# x# = 0.0#
+"timesFloat x 0.0" forall x#. timesFloat# x# 0.0# = 0.0#
+"timesFloat0.0 x" forall x#. timesFloat# 0.0# x# = 0.0#
+"timesFloat x 1.0" forall x#. timesFloat# x# 1.0# = x#
+"timesFloat 1.0 x" forall x#. timesFloat# 1.0# x# = x#
+"divideFloat x 1.0" forall x#. divideFloat# x# 1.0# = x#
+ #-}
+
+{-# RULES
+"plusDouble x 0.0" forall x#. (+##) x# 0.0## = x#
+"plusDouble 0.0 x" forall x#. (+##) 0.0## x# = x#
+"minusDouble x 0.0" forall x#. (-##) x# 0.0## = x#
+"minusDouble x x" forall x#. (-##) x# x# = 0.0##
+"timesDouble x 0.0" forall x#. (*##) x# 0.0## = 0.0##
+"timesDouble 0.0 x" forall x#. (*##) 0.0## x# = 0.0##
+"timesDouble x 1.0" forall x#. (*##) x# 1.0## = x#
+"timesDouble 1.0 x" forall x#. (*##) 1.0## x# = x#
+"divideDouble x 1.0" forall x#. (/##) x# 1.0## = x#
+ #-}
+
-- Wrappers for the shift operations. The uncheckedShift# family are
-- undefined when the amount being shifted by is greater than the size
-- in bits of Int#, so these wrappers perform a check and return
\begin{code}
unpackCString# :: Addr# -> [Char]
{-# NOINLINE [1] unpackCString# #-}
-unpackCString# a = unpackCStringList# a
-
-unpackCStringList# :: Addr# -> [Char]
-unpackCStringList# addr
+unpackCString# addr
= unpack 0#
where
unpack nh
{-# RULES
"unpack" [~1] forall a . unpackCString# a = build (unpackFoldrCString# a)
-"unpack-list" [1] forall a . unpackFoldrCString# a (:) [] = unpackCStringList# a
+"unpack-list" [1] forall a . unpackFoldrCString# a (:) [] = unpackCString# a
"unpack-append" forall a n . unpackFoldrCString# a (:) n = unpackAppendCString# a n
--- There's a built-in rule (in GHC.Rules.lhs) for
+-- There's a built-in rule (in PrelRules.lhs) for
-- unpackFoldr "foo" c (unpackFoldr "baz" c n) = unpackFoldr "foobaz" c n
#-}