[project @ 2005-03-30 11:15:21 by simonmar]
[ghc-base.git] / GHC / Num.lhs
index 52c2a7b..b5e27a8 100644 (file)
@@ -1,22 +1,18 @@
-% ------------------------------------------------------------------------------
-% $Id: Num.lhs,v 1.4 2002/02/05 17:32:26 simonmar Exp $
-%
-% (c) The University of Glasgow, 1994-2000
-%
-
-\section[GHC.Num]{Module @GHC.Num@}
-
-The class
-
-       Num
-
-and the type
-
-       Integer
-
-
 \begin{code}
-{-# OPTIONS -fno-implicit-prelude #-}
+{-# OPTIONS_GHC -fno-implicit-prelude #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  GHC.Num
+-- Copyright   :  (c) The University of Glasgow 1994-2002
+-- License     :  see libraries/base/LICENSE
+-- 
+-- Maintainer  :  cvs-ghc@haskell.org
+-- Stability   :  internal
+-- Portability :  non-portable (GHC Extensions)
+--
+-- The 'Num' class and the 'Integer' type.
+--
+-----------------------------------------------------------------------------
 
 #include "MachDeps.h"
 #if SIZEOF_HSWORD == 4
@@ -27,11 +23,11 @@ and the type
 #error Please define LEFTMOST_BIT to be 2^(SIZEOF_HSWORD*8-1)
 #endif
 
+-- #hide
 module GHC.Num where
 
 import {-# SOURCE #-} GHC.Err
 import GHC.Base
-import GHC.List
 import GHC.Enum
 import GHC.Show
 
@@ -49,15 +45,37 @@ default ()          -- Double isn't available yet,
 %*********************************************************
 
 \begin{code}
+-- | Basic numeric class.
+--
+-- Minimal complete definition: all except 'negate' or @(-)@
 class  (Eq a, Show a) => Num a  where
     (+), (-), (*)      :: a -> a -> a
+    -- | Unary negation.
     negate             :: a -> a
-    abs, signum                :: a -> a
+    -- | Absolute value.
+    abs                        :: a -> a
+    -- | Sign of a number.
+    -- The functions 'abs' and 'signum' should satisfy the law: 
+    --
+    -- > abs x * signum x == x
+    --
+    -- For real numbers, the 'signum' is either @-1@ (negative), @0@ (zero)
+    -- or @1@ (positive).
+    signum             :: a -> a
+    -- | Conversion from an 'Integer'.
+    -- An integer literal represents the application of the function
+    -- 'fromInteger' to the appropriate value of type 'Integer',
+    -- so such literals have type @('Num' a) => a@.
     fromInteger                :: Integer -> a
 
     x - y              = x + negate y
     negate x           = 0 - x
 
+-- | the same as @'flip' ('-')@.
+--
+-- Because @-@ is treated specially in the Haskell grammar,
+-- @(-@ /e/@)@ is not a section, but an application of prefix negation.
+-- However, @('subtract'@ /exp/@)@ is equivalent to the disallowed section.
 {-# INLINE subtract #-}
 subtract :: (Num a) => a -> a -> a
 subtract x y = y - x
@@ -83,15 +101,9 @@ instance  Num Int  where
             | otherwise   = 1
 
     fromInteger = integer2Int
-\end{code}
-
-
-\begin{code}
--- These can't go in GHC.Base with the defn of Int, because
--- we don't have pairs defined at that time!
 
 quotRemInt :: Int -> Int -> (Int, Int)
-a@(I# _) `quotRemInt` b@(I# _) = (a `quotInt` b, a `remInt` b)
+quotRemInt a@(I# _) b@(I# _) = (a `quotInt` b, a `remInt` b)
     -- OK, so I made it a little stricter.  Shoot me.  (WDP 94/10)
 
 divModInt ::  Int -> Int -> (Int, Int)
@@ -99,7 +111,6 @@ divModInt x@(I# _) y@(I# _) = (x `divInt` y, x `modInt` y)
     -- Stricter.  Sorry if you don't like it.  (WDP 94/10)
 \end{code}
 
-
 %*********************************************************
 %*                                                     *
 \subsection{The @Integer@ type}
@@ -107,6 +118,7 @@ divModInt x@(I# _) y@(I# _) = (x `divInt` y, x `modInt` y)
 %*********************************************************
 
 \begin{code}
+-- | Arbitrary-precision integers.
 data Integer   
    = S# Int#                           -- small integers
 #ifndef ILX