diff options
-rw-r--r-- | compiler/GHC/Builtin/primops.txt.pp | 24 | ||||
-rw-r--r-- | compiler/GHC/Core/Opt/ConstantFold.hs | 30 | ||||
-rw-r--r-- | compiler/GHC/StgToCmm/Prim.hs | 24 | ||||
-rw-r--r-- | compiler/GHC/Types/Literal.hs | 62 |
4 files changed, 70 insertions, 70 deletions
diff --git a/compiler/GHC/Builtin/primops.txt.pp b/compiler/GHC/Builtin/primops.txt.pp index 59f31faf57..9cbe75be35 100644 --- a/compiler/GHC/Builtin/primops.txt.pp +++ b/compiler/GHC/Builtin/primops.txt.pp @@ -603,14 +603,14 @@ primop IntLeOp "<=#" Compare Int# -> Int# -> Int# primop ChrOp "chr#" GenPrimOp Int# -> Char# with code_size = 0 -primop Int2WordOp "int2Word#" GenPrimOp Int# -> Word# +primop IntToWordOp "int2Word#" GenPrimOp Int# -> Word# with code_size = 0 -primop Int2FloatOp "int2Float#" GenPrimOp Int# -> Float# -primop Int2DoubleOp "int2Double#" GenPrimOp Int# -> Double# +primop IntToFloatOp "int2Float#" GenPrimOp Int# -> Float# +primop IntToDoubleOp "int2Double#" GenPrimOp Int# -> Double# -primop Word2FloatOp "word2Float#" GenPrimOp Word# -> Float# -primop Word2DoubleOp "word2Double#" GenPrimOp Word# -> Double# +primop WordToFloatOp "word2Float#" GenPrimOp Word# -> Float# +primop WordToDoubleOp "word2Double#" GenPrimOp Word# -> Double# primop ISllOp "uncheckedIShiftL#" GenPrimOp Int# -> Int# -> Int# {Shift left. Result undefined if shift amount is not @@ -696,7 +696,7 @@ primop SrlOp "uncheckedShiftRL#" GenPrimOp Word# -> Int# -> Word# {Shift right logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.} -primop Word2IntOp "word2Int#" GenPrimOp Word# -> Int# +primop WordToIntOp "word2Int#" GenPrimOp Word# -> Int# with code_size = 0 primop WordGtOp "gtWord#" Compare Word# -> Word# -> Int# @@ -844,12 +844,12 @@ primop DoubleNegOp "negateDouble#" GenPrimOp Double# -> Double# primop DoubleFabsOp "fabsDouble#" GenPrimOp Double# -> Double# -primop Double2IntOp "double2Int#" GenPrimOp Double# -> Int# +primop DoubleToIntOp "double2Int#" GenPrimOp Double# -> Int# {Truncates a {\tt Double#} value to the nearest {\tt Int#}. Results are undefined if the truncation if truncation yields a value outside the range of {\tt Int#}.} -primop Double2FloatOp "double2Float#" GenPrimOp Double# -> Float# +primop DoubleToFloatOp "double2Float#" GenPrimOp Double# -> Float# primop DoubleExpOp "expDouble#" GenPrimOp Double# -> Double# @@ -998,7 +998,7 @@ primop FloatNegOp "negateFloat#" GenPrimOp Float# -> Float# primop FloatFabsOp "fabsFloat#" GenPrimOp Float# -> Float# -primop Float2IntOp "float2Int#" GenPrimOp Float# -> Int# +primop FloatToIntOp "float2Int#" GenPrimOp Float# -> Int# {Truncates a {\tt Float#} value to the nearest {\tt Int#}. Results are undefined if the truncation if truncation yields a value outside the range of {\tt Int#}.} @@ -1097,7 +1097,7 @@ primop FloatPowerOp "powerFloat#" GenPrimOp with code_size = { primOpCodeSizeForeignCall } -primop Float2DoubleOp "float2Double#" GenPrimOp Float# -> Double# +primop FloatToDoubleOp "float2Double#" GenPrimOp Float# -> Double# primop FloatDecode_IntOp "decodeFloat_Int#" GenPrimOp Float# -> (# Int#, Int# #) @@ -2283,11 +2283,11 @@ primop AddrSubOp "minusAddr#" GenPrimOp Addr# -> Addr# -> Int# primop AddrRemOp "remAddr#" GenPrimOp Addr# -> Int# -> Int# {Return the remainder when the {\tt Addr\#} arg, treated like an {\tt Int\#}, is divided by the {\tt Int\#} arg.} -primop Addr2IntOp "addr2Int#" GenPrimOp Addr# -> Int# +primop AddrToIntOp "addr2Int#" GenPrimOp Addr# -> Int# {Coerce directly from address to int.} with code_size = 0 deprecated_msg = { This operation is strongly deprecated. } -primop Int2AddrOp "int2Addr#" GenPrimOp Int# -> Addr# +primop IntToAddrOp "int2Addr#" GenPrimOp Int# -> Addr# {Coerce directly from int to address.} with code_size = 0 deprecated_msg = { This operation is strongly deprecated. } diff --git a/compiler/GHC/Core/Opt/ConstantFold.hs b/compiler/GHC/Core/Opt/ConstantFold.hs index 8c44a5d72d..eaf7aa65e4 100644 --- a/compiler/GHC/Core/Opt/ConstantFold.hs +++ b/compiler/GHC/Core/Opt/ConstantFold.hs @@ -193,10 +193,10 @@ primOpRules nm = \case SrlOp -> mkPrimOpRule nm 2 [ shiftRule LitNumWord shiftRightLogical ] -- coercions - Word2IntOp -> mkPrimOpRule nm 1 [ liftLitPlatform word2IntLit - , inversePrimOp Int2WordOp ] - Int2WordOp -> mkPrimOpRule nm 1 [ liftLitPlatform int2WordLit - , inversePrimOp Word2IntOp ] + WordToIntOp -> mkPrimOpRule nm 1 [ liftLitPlatform wordToIntLit + , inversePrimOp IntToWordOp ] + IntToWordOp -> mkPrimOpRule nm 1 [ liftLitPlatform intToWordLit + , inversePrimOp WordToIntOp ] Narrow8IntOp -> mkPrimOpRule nm 1 [ liftLit narrow8IntLit , subsumedByPrimOp Narrow8IntOp , Narrow8IntOp `subsumesPrimOp` Narrow16IntOp @@ -229,19 +229,19 @@ primOpRules nm = \case , subsumedByPrimOp Narrow32WordOp , removeOp32 , narrowSubsumesAnd AndOp Narrow32WordOp 32 ] - OrdOp -> mkPrimOpRule nm 1 [ liftLit char2IntLit + OrdOp -> mkPrimOpRule nm 1 [ liftLit charToIntLit , inversePrimOp ChrOp ] ChrOp -> mkPrimOpRule nm 1 [ do [Lit lit] <- getArgs guard (litFitsInChar lit) - liftLit int2CharLit + liftLit intToCharLit , inversePrimOp OrdOp ] - Float2IntOp -> mkPrimOpRule nm 1 [ liftLit float2IntLit ] - Int2FloatOp -> mkPrimOpRule nm 1 [ liftLit int2FloatLit ] - Double2IntOp -> mkPrimOpRule nm 1 [ liftLit double2IntLit ] - Int2DoubleOp -> mkPrimOpRule nm 1 [ liftLit int2DoubleLit ] + FloatToIntOp -> mkPrimOpRule nm 1 [ liftLit floatToIntLit ] + IntToFloatOp -> mkPrimOpRule nm 1 [ liftLit intToFloatLit ] + DoubleToIntOp -> mkPrimOpRule nm 1 [ liftLit doubleToIntLit ] + IntToDoubleOp -> mkPrimOpRule nm 1 [ liftLit intToDoubleLit ] -- SUP: Not sure what the standard says about precision in the following 2 cases - Float2DoubleOp -> mkPrimOpRule nm 1 [ liftLit float2DoubleLit ] - Double2FloatOp -> mkPrimOpRule nm 1 [ liftLit double2FloatLit ] + FloatToDoubleOp -> mkPrimOpRule nm 1 [ liftLit floatToDoubleLit ] + DoubleToFloatOp -> mkPrimOpRule nm 1 [ liftLit doubleToFloatLit ] -- Float FloatAddOp -> mkPrimOpRule nm 2 [ binaryLit (floatOp2 (+)) @@ -1364,9 +1364,9 @@ builtinBignumRules _ = , rule_passthrough "Word# -> Integer -> Word#" integerToWordName integerFromWordName , rule_passthrough "Int64# -> Integer -> Int64#" integerToInt64Name integerFromInt64Name , rule_passthrough "Word64# -> Integer -> Word64#" integerToWord64Name integerFromWord64Name - , rule_smallIntegerTo "IS -> Word#" integerToWordName Int2WordOp - , rule_smallIntegerTo "IS -> Float" integerToFloatName Int2FloatOp - , rule_smallIntegerTo "IS -> Double" integerToDoubleName Int2DoubleOp + , rule_smallIntegerTo "IS -> Word#" integerToWordName IntToWordOp + , rule_smallIntegerTo "IS -> Float" integerToFloatName IntToFloatOp + , rule_smallIntegerTo "IS -> Double" integerToDoubleName IntToDoubleOp , rule_passthrough "Word# -> Natural -> Word#" naturalToWordName naturalNSDataConName , rule_IntegerToNaturalClamp "Integer -> Natural (clamp)" integerToNaturalClampName diff --git a/compiler/GHC/StgToCmm/Prim.hs b/compiler/GHC/StgToCmm/Prim.hs index 4c69537733..90cb963e89 100644 --- a/compiler/GHC/StgToCmm/Prim.hs +++ b/compiler/GHC/StgToCmm/Prim.hs @@ -840,9 +840,9 @@ emitPrimOp dflags primop = case primop of emitCtzCall res w (wordWidth platform) -- Unsigned int to floating point conversions - Word2FloatOp -> \[w] -> opIntoRegs $ \[res] -> do + WordToFloatOp -> \[w] -> opIntoRegs $ \[res] -> do emitPrimCall [res] (MO_UF_Conv W32) [w] - Word2DoubleOp -> \[w] -> opIntoRegs $ \[res] -> do + WordToDoubleOp -> \[w] -> opIntoRegs $ \[res] -> do emitPrimCall [res] (MO_UF_Conv W64) [w] -- Atomic operations @@ -1056,10 +1056,10 @@ emitPrimOp dflags primop = case primop of -- The rest just translate straightforwardly - Int2WordOp -> \args -> opNop args - Word2IntOp -> \args -> opNop args - Int2AddrOp -> \args -> opNop args - Addr2IntOp -> \args -> opNop args + IntToWordOp -> \args -> opNop args + WordToIntOp -> \args -> opNop args + IntToAddrOp -> \args -> opNop args + AddrToIntOp -> \args -> opNop args ChrOp -> \args -> opNop args -- Int# and Char# are rep'd the same OrdOp -> \args -> opNop args @@ -1309,14 +1309,14 @@ emitPrimOp dflags primop = case primop of -- Conversions - Int2DoubleOp -> \args -> opTranslate args (MO_SF_Conv (wordWidth platform) W64) - Double2IntOp -> \args -> opTranslate args (MO_FS_Conv W64 (wordWidth platform)) + IntToDoubleOp -> \args -> opTranslate args (MO_SF_Conv (wordWidth platform) W64) + DoubleToIntOp -> \args -> opTranslate args (MO_FS_Conv W64 (wordWidth platform)) - Int2FloatOp -> \args -> opTranslate args (MO_SF_Conv (wordWidth platform) W32) - Float2IntOp -> \args -> opTranslate args (MO_FS_Conv W32 (wordWidth platform)) + IntToFloatOp -> \args -> opTranslate args (MO_SF_Conv (wordWidth platform) W32) + FloatToIntOp -> \args -> opTranslate args (MO_FS_Conv W32 (wordWidth platform)) - Float2DoubleOp -> \args -> opTranslate args (MO_FF_Conv W32 W64) - Double2FloatOp -> \args -> opTranslate args (MO_FF_Conv W64 W32) + FloatToDoubleOp -> \args -> opTranslate args (MO_FF_Conv W32 W64) + DoubleToFloatOp -> \args -> opTranslate args (MO_FF_Conv W64 W32) -- Word comparisons masquerading as more exotic things. diff --git a/compiler/GHC/Types/Literal.hs b/compiler/GHC/Types/Literal.hs index 16d4539630..97ab69563a 100644 --- a/compiler/GHC/Types/Literal.hs +++ b/compiler/GHC/Types/Literal.hs @@ -39,13 +39,13 @@ module GHC.Types.Literal , litValue, isLitValue, isLitValue_maybe, mapLitValue -- ** Coercions - , word2IntLit, int2WordLit + , wordToIntLit, intToWordLit , narrowLit , narrow8IntLit, narrow16IntLit, narrow32IntLit , narrow8WordLit, narrow16WordLit, narrow32WordLit - , char2IntLit, int2CharLit - , float2IntLit, int2FloatLit, double2IntLit, int2DoubleLit - , nullAddrLit, rubbishLit, float2DoubleLit, double2FloatLit + , charToIntLit, intToCharLit + , floatToIntLit, intToFloatLit, doubleToIntLit, intToDoubleLit + , nullAddrLit, rubbishLit, floatToDoubleLit, doubleToFloatLit ) where #include "HsVersions.h" @@ -474,27 +474,27 @@ isLitValue = isJust . isLitValue_maybe narrow8IntLit, narrow16IntLit, narrow32IntLit, narrow8WordLit, narrow16WordLit, narrow32WordLit, - char2IntLit, int2CharLit, - float2IntLit, int2FloatLit, double2IntLit, int2DoubleLit, - float2DoubleLit, double2FloatLit + charToIntLit, intToCharLit, + floatToIntLit, intToFloatLit, doubleToIntLit, intToDoubleLit, + floatToDoubleLit, doubleToFloatLit :: Literal -> Literal -word2IntLit, int2WordLit :: Platform -> Literal -> Literal -word2IntLit platform (LitNumber LitNumWord w) +wordToIntLit, intToWordLit :: Platform -> Literal -> Literal +wordToIntLit platform (LitNumber LitNumWord w) -- Map Word range [max_int+1, max_word] -- to Int range [min_int , -1] -- Range [0,max_int] has the same representation with both Int and Word | w > platformMaxInt platform = mkLitInt platform (w - platformMaxWord platform - 1) | otherwise = mkLitInt platform w -word2IntLit _ l = pprPanic "word2IntLit" (ppr l) +wordToIntLit _ l = pprPanic "wordToIntLit" (ppr l) -int2WordLit platform (LitNumber LitNumInt i) +intToWordLit platform (LitNumber LitNumInt i) -- Map Int range [min_int , -1] -- to Word range [max_int+1, max_word] -- Range [0,max_int] has the same representation with both Int and Word | i < 0 = mkLitWord platform (1 + platformMaxWord platform + i) | otherwise = mkLitWord platform i -int2WordLit _ l = pprPanic "int2WordLit" (ppr l) +intToWordLit _ l = pprPanic "intToWordLit" (ppr l) -- | Narrow a literal number (unchecked result range) narrowLit :: forall a. Integral a => Proxy a -> Literal -> Literal @@ -508,25 +508,25 @@ narrow8WordLit = narrowLit (Proxy :: Proxy Word8) narrow16WordLit = narrowLit (Proxy :: Proxy Word16) narrow32WordLit = narrowLit (Proxy :: Proxy Word32) -char2IntLit (LitChar c) = mkLitIntUnchecked (toInteger (ord c)) -char2IntLit l = pprPanic "char2IntLit" (ppr l) -int2CharLit (LitNumber _ i) = LitChar (chr (fromInteger i)) -int2CharLit l = pprPanic "int2CharLit" (ppr l) - -float2IntLit (LitFloat f) = mkLitIntUnchecked (truncate f) -float2IntLit l = pprPanic "float2IntLit" (ppr l) -int2FloatLit (LitNumber _ i) = LitFloat (fromInteger i) -int2FloatLit l = pprPanic "int2FloatLit" (ppr l) - -double2IntLit (LitDouble f) = mkLitIntUnchecked (truncate f) -double2IntLit l = pprPanic "double2IntLit" (ppr l) -int2DoubleLit (LitNumber _ i) = LitDouble (fromInteger i) -int2DoubleLit l = pprPanic "int2DoubleLit" (ppr l) - -float2DoubleLit (LitFloat f) = LitDouble f -float2DoubleLit l = pprPanic "float2DoubleLit" (ppr l) -double2FloatLit (LitDouble d) = LitFloat d -double2FloatLit l = pprPanic "double2FloatLit" (ppr l) +charToIntLit (LitChar c) = mkLitIntUnchecked (toInteger (ord c)) +charToIntLit l = pprPanic "charToIntLit" (ppr l) +intToCharLit (LitNumber _ i) = LitChar (chr (fromInteger i)) +intToCharLit l = pprPanic "intToCharLit" (ppr l) + +floatToIntLit (LitFloat f) = mkLitIntUnchecked (truncate f) +floatToIntLit l = pprPanic "floatToIntLit" (ppr l) +intToFloatLit (LitNumber _ i) = LitFloat (fromInteger i) +intToFloatLit l = pprPanic "intToFloatLit" (ppr l) + +doubleToIntLit (LitDouble f) = mkLitIntUnchecked (truncate f) +doubleToIntLit l = pprPanic "doubleToIntLit" (ppr l) +intToDoubleLit (LitNumber _ i) = LitDouble (fromInteger i) +intToDoubleLit l = pprPanic "intToDoubleLit" (ppr l) + +floatToDoubleLit (LitFloat f) = LitDouble f +floatToDoubleLit l = pprPanic "floatToDoubleLit" (ppr l) +doubleToFloatLit (LitDouble d) = LitFloat d +doubleToFloatLit l = pprPanic "doubleToFloatLit" (ppr l) nullAddrLit :: Literal nullAddrLit = LitNullAddr |