[project @ 2002-09-16 11:24:20 by simonpj]
[ghc-base.git] / GHC / Base.lhs
index 847c1fe..fe42991 100644 (file)
@@ -86,7 +86,7 @@ Other Prelude modules are much easier with fewer complex dependencies.
 module GHC.Base
        (
        module GHC.Base,
-       module GHC.Prim,                -- Re-export GHC.Prim and GHC.Err, to avoid lots
+       module GHC.Prim,        -- Re-export GHC.Prim and GHC.Err, to avoid lots
        module GHC.Err          -- of people having to import it explicitly
   ) 
        where
@@ -149,6 +149,14 @@ unpackCStringUtf8# a = error "urk"
 %*********************************************************
 
 \begin{code}
+
+-- | The 'Eq' class defines equality ('==') and inequality ('/=').
+-- All the basic datatypes exported by the "Prelude" are instances of 'Eq',
+-- and 'Eq' may be derived for any datatype whose constituents are also
+-- instances of 'Eq'.
+--
+-- Minimal complete definition: either '==' or '/='.
+--
 class  Eq a  where
     (==), (/=)          :: a -> a -> Bool
 
@@ -368,21 +376,34 @@ mapFB c f x ys = c (f x) ys
 %*********************************************************
 
 \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}
@@ -402,6 +423,8 @@ need ().  (We could arrange suck in () only if -fglasgow-exts, but putting
 it here seems more direct.)
 
 \begin{code}
+-- | The unit datatype @()@ has one non-undefined member, the nullary
+-- constructor @()@.
 data () = ()
 
 instance Eq () where
@@ -426,6 +449,9 @@ instance Ord () where
 %*********************************************************
 
 \begin{code}
+-- | Represents an ordering relationship between two values: less
+-- than, equal to, or greater than.  An 'Ordering' is returned by
+-- 'compare'.
 data Ordering = LT | EQ | GT deriving (Eq, Ord)
        -- Read in GHC.Read, Show in GHC.Show
 \end{code}
@@ -438,8 +464,18 @@ data Ordering = LT | EQ | GT deriving (Eq, Ord)
 %*********************************************************
 
 \begin{code}
+-- | A 'String' is a list of characters.  String constants in Haskell are values
+-- of type 'String'.
+--
 type String = [Char]
 
+{-| The character type 'Char' is an enumeration whose values represent
+Unicode characters.  A character literal in Haskell has type 'Char'.
+
+To convert a 'Char' to or from an 'Int', use 'Prelude.toEnum' and
+'Prelude.fromEnum' from the 'Enum' class respectively (equivalently
+'ord' and 'chr' also do the trick).
+-}
 data Char = C# Char#
 
 -- We don't use deriving for Eq and Ord, because for Ord the derived
@@ -496,6 +532,10 @@ eqString cs1      cs2         = False
 
 \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#
@@ -547,6 +587,22 @@ compareInt# x# y#
 id                     :: a -> a
 id x                   =  x
 
+-- lazy function; this is just the same as id, but its unfolding
+-- and strictness are over-ridden by the definition in MkId.lhs
+-- That way, it does not get inlined, and the strictness analyser
+-- sees it as lazy.  Then the worker/wrapper phase inlines it.
+-- Result: happiness
+lazy :: a -> a
+lazy x = x
+
+-- Assertion function. This simply ignores its boolean argument.
+-- The compiler may rewrite it to (assertError line)
+--     SLPJ: in 5.04 etc 'assert' is in GHC.Prim,
+--     but from Template Haskell onwards it's simply
+--     defined here in Base.lhs
+assert :: Bool -> a -> a
+assert pred r = r
 -- constant function
 const                  :: a -> b -> a
 const x _              =  x
@@ -619,11 +675,18 @@ data (:*:) a b = a :*: b
 %*********************************************************
 
 \begin{code}
-divInt#, modInt# :: Int# -> Int# -> Int#
+divInt# :: Int# -> Int# -> Int#
 x# `divInt#` y#
-    | (x# ># 0#) && (y# <# 0#) = ((x# -# y#) -# 1#) `quotInt#` y#
-    | (x# <# 0#) && (y# ># 0#) = ((x# -# y#) +# 1#) `quotInt#` y#
+       -- Be careful NOT to overflow if we do any additional arithmetic
+       -- on the arguments...  the following  previous version of this
+       -- code has problems with overflow:
+--    | (x# ># 0#) && (y# <# 0#) = ((x# -# y#) -# 1#) `quotInt#` y#
+--    | (x# <# 0#) && (y# ># 0#) = ((x# -# y#) +# 1#) `quotInt#` y#
+    | (x# ># 0#) && (y# <# 0#) = ((x# -# 1#) `quotInt#` y#) -# 1#
+    | (x# <# 0#) && (y# ># 0#) = ((x# +# 1#) `quotInt#` y#) -# 1#
     | otherwise                = x# `quotInt#` y#
+
+modInt# :: Int# -> Int# -> Int#
 x# `modInt#` y#
     | (x# ># 0#) && (y# <# 0#) ||
       (x# <# 0#) && (y# ># 0#)    = if r# /=# 0# then r# +# y# else 0#
@@ -817,19 +880,19 @@ unpackCStringUtf8# addr
       | ch `eqChar#` '\0'#   = []
       | ch `leChar#` '\x7F'# = C# ch : unpack (nh +# 1#)
       | ch `leChar#` '\xDF'# =
-          C# (chr# ((ord# ch                                  -# 0xC0#) `uncheckedIShiftL#`  6# +#
-                    (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#))) :
+          C# (chr# (((ord# ch                                  -# 0xC0#) `uncheckedIShiftL#`  6#) +#
+                     (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#))) :
           unpack (nh +# 2#)
       | ch `leChar#` '\xEF'# =
-          C# (chr# ((ord# ch                                  -# 0xE0#) `uncheckedIShiftL#` 12# +#
-                    (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `uncheckedIShiftL#`  6# +#
-                    (ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#))) :
+          C# (chr# (((ord# ch                                  -# 0xE0#) `uncheckedIShiftL#` 12#) +#
+                    ((ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `uncheckedIShiftL#`  6#) +#
+                     (ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#))) :
           unpack (nh +# 3#)
       | otherwise            =
-          C# (chr# ((ord# ch                                  -# 0xF0#) `uncheckedIShiftL#` 18# +#
-                    (ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `uncheckedIShiftL#` 12# +#
-                    (ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#) `uncheckedIShiftL#`  6# +#
-                    (ord# (indexCharOffAddr# addr (nh +# 3#)) -# 0x80#))) :
+          C# (chr# (((ord# ch                                  -# 0xF0#) `uncheckedIShiftL#` 18#) +#
+                    ((ord# (indexCharOffAddr# addr (nh +# 1#)) -# 0x80#) `uncheckedIShiftL#` 12#) +#
+                    ((ord# (indexCharOffAddr# addr (nh +# 2#)) -# 0x80#) `uncheckedIShiftL#`  6#) +#
+                     (ord# (indexCharOffAddr# addr (nh +# 3#)) -# 0x80#))) :
           unpack (nh +# 4#)
       where
        ch = indexCharOffAddr# addr nh