diff --git a/ghc/compiler/basicTypes/Unique.lhs b/ghc/compiler/basicTypes/Unique.lhs index 97c99f8bb395af3c022a5fbd01460120091034e1..1282995229f5750cb6d6cccc9c39e048bf626c8d 100644 --- a/ghc/compiler/basicTypes/Unique.lhs +++ b/ghc/compiler/basicTypes/Unique.lhs @@ -114,7 +114,6 @@ module Unique ( integerPlusOneIdKey, integerPlusTwoIdKey, int2IntegerIdKey, - addr2IntegerIdKey, integerTyConKey, integerZeroIdKey, integralClassKey, @@ -625,7 +624,6 @@ integerPlusOneIdKey = mkPreludeMiscIdUnique 10 integerPlusTwoIdKey = mkPreludeMiscIdUnique 11 integerZeroIdKey = mkPreludeMiscIdUnique 12 int2IntegerIdKey = mkPreludeMiscIdUnique 13 -addr2IntegerIdKey = mkPreludeMiscIdUnique 14 irrefutPatErrorIdKey = mkPreludeMiscIdUnique 15 eqStringIdKey = mkPreludeMiscIdUnique 16 noMethodBindingErrorIdKey = mkPreludeMiscIdUnique 17 diff --git a/ghc/compiler/prelude/PrelInfo.lhs b/ghc/compiler/prelude/PrelInfo.lhs index 23c04ce5eb846ab5bfbd1d3985f526247cd39059..cfe7a82b7c9be50e15e16270e1bfae2c966498f2 100644 --- a/ghc/compiler/prelude/PrelInfo.lhs +++ b/ghc/compiler/prelude/PrelInfo.lhs @@ -256,7 +256,6 @@ knownKeyNames , (makeStablePtr_RDR, makeStablePtrIdKey) , (bindIO_RDR, bindIOIdKey) , (returnIO_RDR, returnIOIdKey) - , (addr2Integer_RDR, addr2IntegerIdKey) -- Strings and lists , (map_RDR, mapIdKey) diff --git a/ghc/compiler/prelude/PrelNames.lhs b/ghc/compiler/prelude/PrelNames.lhs index 379dff95e7b982f50c22b37485b22c7d7b30b43d..073bfae1f90ee41ac07d8c4a85f0d60ff60f41d9 100644 --- a/ghc/compiler/prelude/PrelNames.lhs +++ b/ghc/compiler/prelude/PrelNames.lhs @@ -37,8 +37,7 @@ module PrelNames error_RDR, assertErr_RDR, showString_RDR, showParen_RDR, readParen_RDR, lex_RDR, showSpace_RDR, showList___RDR, readList___RDR, negate_RDR, - addr2Integer_RDR, ioTyCon_RDR, - foldr_RDR, build_RDR, getTag_RDR, plusInteger_RDR, timesInteger_RDR, eqString_RDR, + ioTyCon_RDR, foldr_RDR, build_RDR, getTag_RDR, plusInteger_RDR, timesInteger_RDR, eqString_RDR, orderingTyCon_RDR, rationalTyCon_RDR, ratioTyCon_RDR, byteArrayTyCon_RDR, mutableByteArrayTyCon_RDR, foreignObjTyCon_RDR, @@ -268,7 +267,6 @@ minus_RDR = varQual pREL_NUM_Name SLIT("-") negate_RDR = varQual pREL_NUM_Name SLIT("negate") plus_RDR = varQual pREL_NUM_Name SLIT("+") times_RDR = varQual pREL_NUM_Name SLIT("*") -addr2Integer_RDR = varQual pREL_NUM_Name SLIT("addr2Integer") plusInteger_RDR = varQual pREL_NUM_Name SLIT("plusInteger") timesInteger_RDR = varQual pREL_NUM_Name SLIT("timesInteger") diff --git a/ghc/compiler/prelude/primops.txt b/ghc/compiler/prelude/primops.txt index d0212643c011e49329e2c3a3d72ac7e2ec5eede5..5eff2f57a244bfe7729a609f5d160a064b60ebe0 100644 --- a/ghc/compiler/prelude/primops.txt +++ b/ghc/compiler/prelude/primops.txt @@ -1,5 +1,5 @@ ----------------------------------------------------------------------- --- $Id: primops.txt,v 1.4 2000/09/11 12:20:57 sewardj Exp $ +-- $Id: primops.txt,v 1.5 2000/09/26 16:45:34 simonpj Exp $ -- -- Primitive Operations -- @@ -65,10 +65,6 @@ primop AddrLeOp "leAddr#" Compare Addr# -> Addr# -> Bool primop Addr2IntOp "addr2Int#" GenPrimOp Addr# -> Int# -primop Addr2IntegerOp "addr2Integer#" GenPrimOp - Addr# -> (# Int#, ByteArr# #) - with out_of_line = True - ------------------------------------------------------------------------ --- Char# --- diff --git a/ghc/includes/PrimOps.h b/ghc/includes/PrimOps.h index 3411d51699e26afc661345be57de8cf259f88b3e..71bc8afea55622c3267d1c1a1ee8bdc2c37be5f0 100644 --- a/ghc/includes/PrimOps.h +++ b/ghc/includes/PrimOps.h @@ -1,5 +1,5 @@ /* ----------------------------------------------------------------------------- - * $Id: PrimOps.h,v 1.62 2000/09/11 11:17:09 sewardj Exp $ + * $Id: PrimOps.h,v 1.63 2000/09/26 16:45:34 simonpj Exp $ * * (c) The GHC Team, 1998-1999 * @@ -439,7 +439,6 @@ EXTFUN_RTS(divModIntegerzh_fast); /* Conversions */ EXTFUN_RTS(int2Integerzh_fast); EXTFUN_RTS(word2Integerzh_fast); -EXTFUN_RTS(addr2Integerzh_fast); /* Floating-point decodings */ EXTFUN_RTS(decodeFloatzh_fast); diff --git a/ghc/lib/std/PrelBase.lhs b/ghc/lib/std/PrelBase.lhs index 315469da3b56bf128c71fd616596d4a98dcf5d50..f1e7c55be8fb22d352c1142cb916b0697efb75a4 100644 --- a/ghc/lib/std/PrelBase.lhs +++ b/ghc/lib/std/PrelBase.lhs @@ -1,5 +1,5 @@ % ----------------------------------------------------------------------------- -% $Id: PrelBase.lhs,v 1.37 2000/09/07 09:10:07 simonpj Exp $ +% $Id: PrelBase.lhs,v 1.38 2000/09/26 16:45:34 simonpj Exp $ % % (c) The University of Glasgow, 1992-2000 % @@ -79,14 +79,12 @@ module PrelBase ( module PrelBase, module PrelGHC, -- Re-export PrelGHC, PrelErr & PrelNum, to avoid lots - module PrelErr, -- of people having to import it explicitly - module PrelNum + module PrelErr -- of people having to import it explicitly ) where import PrelGHC import {-# SOURCE #-} PrelErr -import {-# SOURCE #-} PrelNum infixr 9 . infixr 5 ++, : @@ -146,11 +144,8 @@ unpackCStringUtf8# a = error "urk" class Eq a where (==), (/=) :: a -> a -> Bool --- x /= y = not (x == y) --- x == y = not (x /= y) --- x /= y = True - (/=) x y = not ((==) x y) - x == y = True + (/=) x y = not ((==) x y) + (==) x y = not ((/=) x y) class (Eq a) => Ord a where compare :: a -> a -> Ordering @@ -261,7 +256,7 @@ foldr :: (a -> b -> b) -> b -> [a] -> b foldr k z xs = go xs where go [] = z - go (x:xs) = x `k` go xs + go (y:ys) = y `k` go ys build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] {-# INLINE 2 build #-} @@ -312,6 +307,7 @@ map :: (a -> b) -> [a] -> [b] map = mapList -- Note eta expanded +mapFB :: (elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst mapFB c f x ys = c (f x) ys mapList :: (a -> b) -> [a] -> [b] diff --git a/ghc/lib/std/PrelGHC.hi-boot b/ghc/lib/std/PrelGHC.hi-boot index 6ccc4d1c0dddf8bb5d53a29a5fab7f81acb3c7af..13f4aac59754bb32195895e454225a9c2d3d17d1 100644 --- a/ghc/lib/std/PrelGHC.hi-boot +++ b/ghc/lib/std/PrelGHC.hi-boot @@ -123,7 +123,6 @@ __export PrelGHC leAddrzh int2Addrzh addr2Intzh - addr2Integerzh Floatzh gtFloatzh diff --git a/ghc/lib/std/PrelNum.lhs b/ghc/lib/std/PrelNum.lhs index 293935821bd079365f7dcfa01f2b715beabd3ab5..31d5c7a1e2c1003fd2e5dac9ee2a8dba34d1a487 100644 --- a/ghc/lib/std/PrelNum.lhs +++ b/ghc/lib/std/PrelNum.lhs @@ -1,5 +1,5 @@ % ------------------------------------------------------------------------------ -% $Id: PrelNum.lhs,v 1.33 2000/09/25 12:58:39 simonpj Exp $ +% $Id: PrelNum.lhs,v 1.34 2000/09/26 16:45:34 simonpj Exp $ % % (c) The University of Glasgow, 1994-2000 % @@ -129,10 +129,6 @@ integer2Int :: Integer -> Int integer2Int (S# i) = I# i integer2Int (J# s d) = case (integer2Int# s d) of { n# -> I# n# } -addr2Integer :: Addr# -> Integer -{-# INLINE addr2Integer #-} -addr2Integer x = case addr2Integer# x of (# s, d #) -> J# s d - toBig (S# i) = case int2Integer# i of { (# s, d #) -> J# s d } toBig i@(J# _ _) = i \end{code} diff --git a/ghc/rts/PrimOps.hc b/ghc/rts/PrimOps.hc index 74575d7a3efd5c7282683b1ac7b0910e9b9a7804..f5c45f30848e6319cc03ae337ad0b9d8efec87ff 100644 --- a/ghc/rts/PrimOps.hc +++ b/ghc/rts/PrimOps.hc @@ -1,5 +1,5 @@ /* ----------------------------------------------------------------------------- - * $Id: PrimOps.hc,v 1.54 2000/08/25 13:12:07 simonmar Exp $ + * $Id: PrimOps.hc,v 1.55 2000/09/26 16:45:35 simonpj Exp $ * * (c) The GHC Team, 1998-2000 * @@ -504,30 +504,6 @@ FN_(word2Integerzh_fast) FE_ } -FN_(addr2Integerzh_fast) -{ - MP_INT result; - char *str; - FB_ - - MAYBE_GC(NO_PTRS,addr2Integerzh_fast); - - /* args: R1 :: Addr# */ - str = R1.a; - - /* Perform the operation */ - if (RET_STGCALL3(int, mpz_init_set_str,&result,(str),/*base*/10)) - abort(); - - /* returns (# size :: Int#, - data :: ByteArray# - #) - */ - TICK_RET_UNBOXED_TUP(2); - RET_NP(result._mp_size, - result._mp_d - sizeofW(StgArrWords)); - FE_ -} /* * 'long long' primops for converting to/from Integers.