X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=GHC%2FNum.lhs;h=67c7b184d46a62349a64ae7106cb3491b88c8f1d;hb=5528dbcc57b17d3006243d8faf130167b29b60f8;hp=a0c61e7ba76c1616dd47bba66ab181c6fb1a41c9;hpb=789216806265506d3b4637b3b22eb5a46eb5f8f8;p=haskell-directory.git diff --git a/GHC/Num.lhs b/GHC/Num.lhs index a0c61e7..67c7b18 100644 --- a/GHC/Num.lhs +++ b/GHC/Num.lhs @@ -1,5 +1,5 @@ \begin{code} -{-# OPTIONS -fno-implicit-prelude #-} +{-# OPTIONS_GHC -fno-implicit-prelude #-} ----------------------------------------------------------------------------- -- | -- Module : GHC.Num @@ -17,17 +17,23 @@ #include "MachDeps.h" #if SIZEOF_HSWORD == 4 #define LEFTMOST_BIT 2147483648 +#define DIGITS 9 +#define BASE 1000000000 #elif SIZEOF_HSWORD == 8 #define LEFTMOST_BIT 9223372036854775808 +#define DIGITS 18 +#define BASE 1000000000000000000 #else #error Please define LEFTMOST_BIT to be 2^(SIZEOF_HSWORD*8-1) +-- DIGITS should be the largest integer such that 10^DIGITS < LEFTMOST_BIT +-- BASE should be 10^DIGITS. Note that ^ is not available yet. #endif +-- #hide module GHC.Num where import {-# SOURCE #-} GHC.Err import GHC.Base -import GHC.List import GHC.Enum import GHC.Show @@ -45,15 +51,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 @@ -79,15 +107,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) @@ -95,7 +117,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} @@ -163,8 +184,8 @@ divModInteger (J# s1 d1) (J# s2 d2) -> (J# s3 d3, J# s4 d4) remInteger :: Integer -> Integer -> Integer -remInteger ia 0 - = error "Prelude.Integral.rem{Integer}: divide by 0" +remInteger ia ib + | ib == 0 = error "Prelude.Integral.rem{Integer}: divide by 0" remInteger a@(S# (-LEFTMOST_BIT#)) b = remInteger (toBig a) b remInteger (S# a) (S# b) = S# (remInt# a b) {- Special case doesn't work, because a 1-element J# has the range @@ -184,8 +205,8 @@ remInteger (J# sa a) (J# sb b) = case remInteger# sa a sb b of (# sr, r #) -> J# sr r quotInteger :: Integer -> Integer -> Integer -quotInteger ia 0 - = error "Prelude.Integral.quot{Integer}: divide by 0" +quotInteger ia ib + | ib == 0 = error "Prelude.Integral.quot{Integer}: divide by 0" quotInteger a@(S# (-LEFTMOST_BIT#)) b = quotInteger (toBig a) b quotInteger (S# a) (S# b) = S# (quotInt# a b) {- Special case disabled, see remInteger above @@ -442,17 +463,81 @@ instance Show Integer where | otherwise = jtos n r showList = showList__ (showsPrec 0) +-- Divide an conquer implementation of string conversion jtos :: Integer -> String -> String jtos n cs | n < 0 = '-' : jtos' (-n) cs | otherwise = jtos' n cs where jtos' :: Integer -> String -> String - jtos' n' cs' - | n' < 10 = case unsafeChr (ord '0' + fromInteger n') of - c@(C# _) -> c:cs' - | otherwise = case unsafeChr (ord '0' + fromInteger r) of - c@(C# _) -> jtos' q (c:cs') + jtos' n cs + | n < BASE = jhead (fromInteger n) cs + | otherwise = jprinth (jsplitf (BASE*BASE) n) cs + + -- Split n into digits in base p. We first split n into digits + -- in base p*p and then split each of these digits into two. + -- Note that the first 'digit' modulo p*p may have a leading zero + -- in base p that we need to drop - this is what jsplith takes care of. + -- jsplitb the handles the remaining digits. + jsplitf :: Integer -> Integer -> [Integer] + jsplitf p n + | p > n = [n] + | otherwise = jsplith p (jsplitf (p*p) n) + + jsplith :: Integer -> [Integer] -> [Integer] + jsplith p (n:ns) = + if q > 0 then fromInteger q : fromInteger r : jsplitb p ns + else fromInteger r : jsplitb p ns + where + (q, r) = n `quotRemInteger` p + + jsplitb :: Integer -> [Integer] -> [Integer] + jsplitb p [] = [] + jsplitb p (n:ns) = q : r : jsplitb p ns where - (q,r) = n' `quotRemInteger` 10 + (q, r) = n `quotRemInteger` p + + -- Convert a number that has been split into digits in base BASE^2 + -- this includes a last splitting step and then conversion of digits + -- that all fit into a machine word. + jprinth :: [Integer] -> String -> String + jprinth (n:ns) cs = + if q > 0 then jhead q $ jblock r $ jprintb ns cs + else jhead r $ jprintb ns cs + where + (q', r') = n `quotRemInteger` BASE + q = fromInteger q' + r = fromInteger r' + + jprintb :: [Integer] -> String -> String + jprintb [] cs = cs + jprintb (n:ns) cs = jblock q $ jblock r $ jprintb ns cs + where + (q', r') = n `quotRemInteger` BASE + q = fromInteger q' + r = fromInteger r' + + -- Convert an integer that fits into a machine word. Again, we have two + -- functions, one that drops leading zeros (jhead) and one that doesn't + -- (jblock) + jhead :: Int -> String -> String + jhead n cs + | n < 10 = case unsafeChr (ord '0' + n) of + c@(C# _) -> c : cs + | otherwise = case unsafeChr (ord '0' + r) of + c@(C# _) -> jhead q (c : cs) + where + (q, r) = n `quotRemInt` 10 + + jblock = jblock' {- ' -} DIGITS + + jblock' :: Int -> Int -> String -> String + jblock' d n cs + | d == 1 = case unsafeChr (ord '0' + n) of + c@(C# _) -> c : cs + | otherwise = case unsafeChr (ord '0' + r) of + c@(C# _) -> jblock' (d - 1) q (c : cs) + where + (q, r) = n `quotRemInt` 10 + \end{code}