Proposal for new numeric bytecode representation: 1) Depreciate the current numeric bytecodes (values 97 - 132) 2) Add a new bytecode INT_PRIM (value 138) which takes a W8 argument 3) Add a new bytecode FLOAT_PRIM (value 139) which takes a W8 argument 4) Add a new bytecode PTR_PRIM (value 140) which takes a W8 argument 5) Support the following numeric types in the runtime: * Word8, Word16, Word32, Word64 * Int8, Int16, Int32 = Int, Int64 * Float, Double, Quad ??, CLDouble ?? * #DataPtr, #CodePtr (to build the FFI interface upon) * Types that map to different concrete machine types on different platforms (except the pointer types) are handled with platform-specific Prelude bytecode that constructs the appropriate typeclass dictionaries, and with platform-specific heap node representations in the runtime system. This includes most of the types from Foreign.C.Types. 6) Encode integer operations into the byte argument of INT_PRIM as follows: 00zzaaaa unsigned arithmetic operations 01zzaaaa signed arithmetic operations 10zzllll logical operations 110zzccc unsigned conversions 111zzccc signed conversions zz operand size(s) 00 = 8-bits 01 = 16-bits 10 = 32-bits 11 = 64-bits ccc conversion specifier 000 = toEnum :: Int32 -> a 001 = fromEnum :: a -> Int32 010 = toInteger :: a -> Integer 011 = fromInteger :: Integer -> a 100 = minBound :: a 101 = maxBound :: a 110 = 111 = aaaa arithmetic operation specifier 0x0 = negate :: a -> a 0x1 = add :: a -> a -> a 0x2 = subtract :: a -> a -> a 0x3 = multiply :: a -> a -> a 0x4 = integer quotient :: a -> a -> a 0x5 = integer remainder :: a -> a -> a 0x6 = (==) :: a -> a -> Bool 0x7 = (/=) :: a -> a -> Bool 0x8 = (<) :: a -> a -> Bool 0x9 = (<=) :: a -> a -> Bool 0xA = (>) :: a -> a -> Bool 0xB = (>=) :: a -> a -> Bool 0xC = succ :: a -> a 0xD = pred :: a -> a 0xE = abs :: a -> a 0xF = signum :: a -> a llll logical operation specifier 0x0 = bit :: Int32 -> a 0x1 = bit test :: a -> Int32 -> Bool 0x2 = bit set :: a -> Int32 -> a 0x3 = complementBit :: a -> Int32 -> a 0x4 = shiftl :: a -> Int32 -> a 0x5 = shiftr :: a -> Int32 -> a 0x6 = rotatel :: a -> Int32 -> a 0x7 = rotater :: a -> Int32 -> a 0x8 = popcount :: a -> Int32 0x9 = lsb :: a -> Int32 0xA = msb :: a -> Int32 0xB = complement :: a -> a 0xC = and :: a -> a -> a 0xD = or :: a -> a -> a 0xF = xor :: a -> a -> a 7) Encode floating-point operations into the argument of FLOAT_PRIM as follows: ppffffff floating-point primitive operation pp floating-point precision 00 = IEEE 754 single-precision 01 = IEEE 754 double-precision 10 = Quad ?? 11 = CLDouble (C99 long double) ?? ffffff floating-point operation specifier 0x00 = zero :: a 0x01 = one :: a 0x02 = pi :: a 0x03 = e :: a 0x04 = fromRational :: Integer -> Integer -> a 0x05 = toRational :: a -> (# Integer, Integer #) 0x06 = abs :: a -> a 0x07 = signum :: a -> a 0x08 = recip :: a -> a 0x09 = truncate :: a -> Integer 0x0A = round :: a -> Integer 0x0B = ceiling :: a -> Integer 0x0C = floor :: a -> Integer 0x0D = encodeFloat :: Integer -> Int32 -> a 0x0E = decodeFloat :: a -> (# Integer, Int32 #) 0x0F = significand :: a -> a 0x10 = toFloatBits :: a -> Integer 0x11 = fromFloatBits :: Integer -> a 0x12 = scaleFloat :: Int32 -> a -> a 0x13 = isNan :: a -> Bool 0x14 = isInfinite :: a -> Bool 0x15 = isDenormalized :: a -> Bool 0x16 = isNegativeZero :: a -> Bool 0x17 = exp :: a -> a 0x18 = log :: a -> a 0x19 = sqrt :: a -> a 0x1A = sin :: a -> a 0x1B = cos :: a -> a 0x1C = tan :: a -> a 0x1D = asin :: a -> a 0x1E = acos :: a -> a 0x1F = atan :: a -> a 0x20 = sinh :: a -> a 0x21 = cosh :: a -> a 0x22 = tanh :: a -> a 0x23 = asinh :: a -> a 0x24 = acosh :: a -> a 0x25 = atanh :: a -> a 0x26 = atan2 :: a -> a -> a 0x27 = (**) :: a -> a -> a 0x28 = logBase :: a -> a -> a 0x29 = add :: a -> a -> a 0x2A = sub :: a -> a -> a 0x2B = mul :: a -> a -> a 0x2C = divide :: a -> a -> a 0x2D = negate :: a -> a 0x2E = succ :: a -> a 0x2F = pred :: a -> a 0x30 = toEnum :: Int32 -> a 0x31 = fromEnum :: a -> Int32 0x32 = (==) :: a -> Bool 0x33 = (/=) :: a -> Bool 0x34 = (<) :: a -> a -> Bool 0x35 = (<=) :: a -> a -> Bool 0x36 = (>) :: a -> a -> Bool 0x37 = (>=) :: a -> a -> Bool 0x38 = 0x39 = 0x3A = 0x3B = 0x3C = 0x3D = 0x3E = 0x3F = 8) Encode pointer operations into the argument of PTR_PRIM as follows: 0kkktttt data marshalling operations 10zzaaaa pointer arithmetic 11------ tttt primitive type identifier 0x0 = Word8 0x1 = Word16 0x2 = Word32 0x3 = Word64 0x4 = Int8 0x5 = Int16 0x6 = Int32 0x7 = Int64 0x8 = Float 0x9 = Double 0xA = Quad ?? 0xB = CLDouble ?? 0xC = #DataPtr 0xD = #CodePtr 0xE = 0xF = kkk marshalling operations 000 = sizeof :: Int32 001 = alignment :: Int32 010 = peek :: #DataPtr -> IO k 011 = poke :: #DataPtr -> k -> IO k 100 = peekElemOff :: #DataPtr -> Int32 -> IO k 101 = pookElemOff :: #DataPtr -> Int32 -> k -> IO () 110 = peekByteOff :: #DataPtr -> Int32 -> IO k 111 = pokeByteOff :: #DataPtr -> Int32 -> k -> IO k zz pointer type 00 = #DataPtr 01 = #CodePtr 10 = 11 = aaaa pointer arithmetic 0x0 = nullPtr :: z 0x1 = plusPtr :: z -> Int32 -> z 0x2 = alignPtr :: z -> Int32 -> z 0x3 = minusPtr :: z -> z -> Int32 0x4 = (==) :: z -> z -> Bool 0x5 = (/=) :: z -> z -> Bool 0x6 = (<) :: z -> z -> Bool 0x7 = (<=) :: z -> z -> Bool 0x8 = (>) :: z -> z -> Bool 0x9 = (>=) :: z -> z -> Bool 0xA = isNull :: z -> Bool 0xB = toInteger :: z -> Integer (not exposed to users, just for Show) 0xC = 0xD = 0xE = 0xF =