[project @ 2000-07-16 21:10:48 by panne]
[ghc-hetmet.git] / ghc / compiler / prelude / PrelRules.lhs
index 5f2c0df..0b54318 100644 (file)
@@ -3,6 +3,10 @@
 %
 \section[ConFold]{Constant Folder}
 
+Conceptually, constant folding should be parameterized with the kind
+of target machine to get identical behaviour during compilation time
+and runtime. We cheat a little bit here...
+
 ToDo:
    check boundaries before folding, e.g. we can fold the Float addition
    (i1 + i2) only if it results        in a valid Float.
@@ -13,8 +17,7 @@ module PrelRules ( primOpRule, builtinRules ) where
 #include "HsVersions.h"
 
 import CoreSyn
-import Rules           ( ProtoCoreRule(..) )
-import Id              ( idUnfolding, mkWildId, isDataConId_maybe )
+import Id              ( mkWildId )
 import Literal         ( Literal(..), isLitLitLit, mkMachInt, mkMachWord
                        , inIntRange, inWordRange, literalType
                        , word2IntLit, int2WordLit, char2IntLit, int2CharLit
@@ -25,32 +28,19 @@ import RdrName              ( RdrName )
 import PrimOp          ( PrimOp(..), primOpOcc )
 import TysWiredIn      ( trueDataConId, falseDataConId )
 import TyCon           ( tyConDataConsIfAvailable, isEnumerationTyCon, isNewTyCon )
-import DataCon         ( DataCon, dataConTag, dataConRepArity, dataConTyCon, dataConId, fIRST_TAG )
-import CoreUnfold      ( maybeUnfoldingTemplate )
+import DataCon         ( dataConTag, dataConTyCon, dataConId, fIRST_TAG )
 import CoreUtils       ( exprIsValue, cheapEqExpr, exprIsConApp_maybe )
 import Type            ( splitTyConApp_maybe )
 import OccName         ( occNameUserString)
 import PrelNames       ( unpackCStringFoldr_RDR )
 import Unique          ( unpackCStringFoldrIdKey, hasKey )
-import Maybes          ( maybeToBool )
-import Char            ( ord, chr )
 import Bits            ( Bits(..) )
-import PrelAddr                ( wordToInt )
 import Word            ( Word64 )
 import Outputable
-
-#if __GLASGOW_HASKELL__ > 405
-import PrelAddr ( intToWord )
-#else
-import PrelAddr ( Word(..) )
-import PrelGHC  ( int2Word# )
-intToWord :: Int -> Word
-intToWord (I# i#) = W# (int2Word# i#)
-#endif
+import CmdLineOpts      ( opt_SimplStrictFP )
 \end{code}
 
 
-
 \begin{code}
 primOpRule :: PrimOp -> CoreRule
 primOpRule op 
@@ -197,12 +187,12 @@ cmpOp cmp name l1 l2
 
 negOp name (MachFloat f)  = Just (name, mkFloatVal (-f))
 negOp name (MachDouble d) = Just (name, mkDoubleVal (-d))
-negOp name l@(MachInt i)  = intResult name (ppr l) (-i)
+negOp name l@(MachInt i)  = intResult name (-i)
 negOp name l             = Nothing
 
 --------------------------
 intOp2 op name l1@(MachInt i1) l2@(MachInt i2)
-  = intResult name (ppr l1 <+> ppr l2) (i1 `op` i2)
+  = intResult name (i1 `op` i2)
 intOp2 op name l1 l2 = Nothing         -- Could find LitLit
 
 intOp2Z op name (MachInt i1) (MachInt i2)
@@ -212,8 +202,7 @@ intOp2Z op name l1 l2 = Nothing             -- LitLit or zero dividend
 --------------------------
 -- Integer is not an instance of Bits, so we operate on Word64
 wordBitOp2 op name l1@(MachWord w1) l2@(MachWord w2)
-  = wordResult name (ppr l1 <+> ppr l2)
-                    ((fromIntegral::Word64->Integer) (fromIntegral w1 `op` fromIntegral w2))
+  = Just (name, mkWordVal ((fromIntegral::Word64->Integer) (fromIntegral w1 `op` fromIntegral w2)))
 wordBitOp2 op name l1 l2 = Nothing             -- Could find LitLit
 
 wordOp2Z op name (MachWord w1) (MachWord w2)
@@ -226,7 +215,7 @@ floatOp2  op name (MachFloat f1) (MachFloat f2)
 floatOp2  op name l1 l2 = Nothing
 
 floatOp2Z op name (MachFloat f1) (MachFloat f2)
-  | f1 /= 0   = Just (name, mkFloatVal (f1 `op` f2))
+  | f2 /= 0   = Just (name, mkFloatVal (f1 `op` f2))
 floatOp2Z op name l1 l2 = Nothing
 
 --------------------------
@@ -235,7 +224,7 @@ doubleOp2  op name (MachDouble f1) (MachDouble f2)
 doubleOp2 op name l1 l2 = Nothing
 
 doubleOp2Z op name (MachDouble f1) (MachDouble f2)
-  | f1 /= 0   = Just (name, mkDoubleVal (f1 `op` f2))
+  | f2 /= 0   = Just (name, mkDoubleVal (f1 `op` f2))
 doubleOp2Z op name l1 l2 = Nothing
 
 
@@ -276,31 +265,14 @@ do_lit_eq is_eq name lit expr
     val_if_neq | is_eq     = falseVal
               | otherwise = trueVal
 
--- TODO: Merge intResult/wordResult
-intResult name pp_args result
-  | not (inIntRange result)
-       -- Better tell the user that we've overflowed...
-       -- ..not that it stops us from actually folding!
-  
-  = pprTrace "Warning:" (text "Integer overflow in:" <+> ppr name <+> pp_args)
-    Just (name, mkIntVal (squashInt result))
-
-  | otherwise
-  = Just (name, mkIntVal result)
-
-wordResult name pp_args result
-  | not (inWordRange result)
-       -- Better tell the user that we've overflowed...
-       -- ..not that it stops us from actually folding!
-  
-  = pprTrace "Warning:" (text "Word overflow in:" <+> ppr name <+> pp_args)
-    Just (name, mkWordVal (squashInt result))
-
-  | otherwise
-  = Just (name, mkWordVal result)
-
-squashInt :: Integer -> Integer        -- Squash into Int range
-squashInt i = toInteger ((fromInteger i)::Int)
+-- Note that we *don't* warn the user about overflow. It's not done at
+-- runtime either, and compilation of completely harmless things like
+--    ((124076834 :: Word32) + (2147483647 :: Word32))
+-- would yield a warning. Instead we simply squash the value into the
+-- Int range, but not in a way suitable for cross-compiling... :-(
+intResult :: RuleName -> Integer -> Maybe (RuleName, CoreExpr)
+intResult name result
+  = Just (name, mkIntVal (toInteger ((fromInteger result)::Int)))
 \end{code}
 
 
@@ -319,21 +291,31 @@ or_rule r1 r2 args = case r1 args of
                   Nothing    -> r2 args
 
 twoLits :: (Literal -> Literal -> Maybe (RuleName, CoreExpr)) -> RuleFun
-twoLits rule [Lit l1, Lit l2] = rule l1 l2
+twoLits rule [Lit l1, Lit l2] = rule (convFloating l1) (convFloating l2)
 twoLits rule other           = Nothing
 
 oneLit :: (Literal -> Maybe (RuleName, CoreExpr)) -> RuleFun
-oneLit rule [Lit l1] = rule l1
+oneLit rule [Lit l1] = rule (convFloating l1)
 oneLit rule other    = Nothing
 
+-- When we strictfp is requested, cut down the precision of the Rational value
+-- to that of Float/Double. We confuse host architecture and target architecture
+-- here, but it's convenient (and wrong :-).
+convFloating :: Literal -> Literal
+convFloating (MachFloat  f) | opt_SimplStrictFP =
+   MachFloat  (toRational ((fromRational f) :: Float ))
+convFloating (MachDouble d) | opt_SimplStrictFP =
+   MachDouble (toRational ((fromRational d) :: Double))
+convFloating l = l
+
 
 trueVal       = Var trueDataConId
 falseVal      = Var falseDataConId
 mkIntVal    i = Lit (mkMachInt  i)
 mkWordVal   w = Lit (mkMachWord w)
 mkCharVal   c = Lit (MachChar   c)
-mkFloatVal  f = Lit (MachFloat  f)
-mkDoubleVal d = Lit (MachDouble d)
+mkFloatVal  f = Lit (convFloating (MachFloat  f))
+mkDoubleVal d = Lit (convFloating (MachDouble d))
 \end{code}