diff options
Diffstat (limited to 'compiler/coreSyn')
| -rw-r--r-- | compiler/coreSyn/CorePrep.hs | 76 | ||||
| -rw-r--r-- | compiler/coreSyn/CoreUnfold.hs | 3 | ||||
| -rw-r--r-- | compiler/coreSyn/CoreUtils.hs | 19 | ||||
| -rw-r--r-- | compiler/coreSyn/MkCore.hs | 10 | 
4 files changed, 83 insertions, 25 deletions
| diff --git a/compiler/coreSyn/CorePrep.hs b/compiler/coreSyn/CorePrep.hs index 75301791b4..9c2954d4ef 100644 --- a/compiler/coreSyn/CorePrep.hs +++ b/compiler/coreSyn/CorePrep.hs @@ -8,8 +8,9 @@ Core pass to saturate constructors and PrimOps  {-# LANGUAGE BangPatterns, CPP, MultiWayIf #-}  module CorePrep ( -      corePrepPgm, corePrepExpr, cvtLitInteger, -      lookupMkIntegerName, lookupIntegerSDataConName +      corePrepPgm, corePrepExpr, cvtLitInteger, cvtLitNatural, +      lookupMkIntegerName, lookupIntegerSDataConName, +      lookupMkNaturalName, lookupNaturalSDataConName    ) where  #include "HsVersions.h" @@ -122,11 +123,13 @@ The goal of this pass is to prepare for code generation.      special case where we use the S# constructor for Integers that      are in the range of Int. -11. Uphold tick consistency while doing this: We move ticks out of +11. Same for LitNatural. + +12. Uphold tick consistency while doing this: We move ticks out of      (non-type) applications where we can, and make sure that we      annotate according to scoping rules when floating. -12. Collect cost centres (including cost centres in unfoldings) if we're in +13. Collect cost centres (including cost centres in unfoldings) if we're in      profiling mode. We have to do this here beucase we won't have unfoldings      after this pass (see `zapUnfolding` and Note [Drop unfoldings and rules]. @@ -608,9 +611,12 @@ cpeRhsE :: CorePrepEnv -> CoreExpr -> UniqSM (Floats, CpeRhs)  cpeRhsE _env expr@(Type {})      = return (emptyFloats, expr)  cpeRhsE _env expr@(Coercion {})  = return (emptyFloats, expr) -cpeRhsE env (Lit (LitInteger i _)) +cpeRhsE env (Lit (LitNumber LitNumInteger i _))      = cpeRhsE env (cvtLitInteger (cpe_dynFlags env) (getMkIntegerId env)                     (cpe_integerSDataCon env) i) +cpeRhsE env (Lit (LitNumber LitNumNatural i _)) +    = cpeRhsE env (cvtLitNatural (cpe_dynFlags env) (getMkNaturalId env) +                   (cpe_naturalSDataCon env) i)  cpeRhsE _env expr@(Lit {}) = return (emptyFloats, expr)  cpeRhsE env expr@(Var {})  = cpeApp env expr  cpeRhsE env expr@(App {}) = cpeApp env expr @@ -693,6 +699,24 @@ cvtLitInteger dflags mk_integer _ i          bits = 31          mask = 2 ^ bits - 1 +cvtLitNatural :: DynFlags -> Id -> Maybe DataCon -> Integer -> CoreExpr +-- Here we convert a literal Natural to the low-level +-- representation. +-- See Note [Natural literals] in Literal +cvtLitNatural dflags _ (Just sdatacon) i +  | inWordRange dflags i -- Special case for small naturals +    = mkConApp sdatacon [Lit (mkMachWord dflags i)] + +cvtLitNatural dflags mk_natural _ i +    = mkApps (Var mk_natural) [words] +  where words = mkListExpr wordTy (f i) +        f 0 = [] +        f x = let low  = x .&. mask +                  high = x `shiftR` bits +              in mkConApp wordDataCon [Lit (mkMachWord dflags low)] : f high +        bits = 32 +        mask = 2 ^ bits - 1 +  -- ---------------------------------------------------------------------------  --              CpeBody: produces a result satisfying CpeBody  -- --------------------------------------------------------------------------- @@ -1388,8 +1412,8 @@ canFloatFromNoCaf platform (Floats ok_to_spec fs) rhs      -- the new binding is static. However it can't mention      -- any non-static things or it would *already* be Caffy      rhs_ok = rhsIsStatic platform (\_ -> False) -                         (\i -> pprPanic "rhsIsStatic" (integer i)) -                         -- Integer literals should not show up +                         (\_nt i -> pprPanic "rhsIsStatic" (integer i)) +                         -- Integer or Natural literals should not show up  wantFloatNested :: RecFlag -> Demand -> Bool -> Floats -> CpeRhs -> Bool  wantFloatNested is_rec dmd is_unlifted floats rhs @@ -1498,7 +1522,9 @@ data CorePrepEnv          --      see Note [lazyId magic], Note [Inlining in CorePrep]          --      and Note [CorePrep inlines trivial CoreExpr not Id] (#12076)          , cpe_mkIntegerId     :: Id +        , cpe_mkNaturalId     :: Id          , cpe_integerSDataCon :: Maybe DataCon +        , cpe_naturalSDataCon :: Maybe DataCon      }  lookupMkIntegerName :: DynFlags -> HscEnv -> IO Id @@ -1506,13 +1532,24 @@ lookupMkIntegerName dflags hsc_env      = guardIntegerUse dflags $ liftM tyThingId $        lookupGlobal hsc_env mkIntegerName +lookupMkNaturalName :: DynFlags -> HscEnv -> IO Id +lookupMkNaturalName dflags hsc_env +    = guardNaturalUse dflags $ liftM tyThingId $ +      lookupGlobal hsc_env mkNaturalName +  lookupIntegerSDataConName :: DynFlags -> HscEnv -> IO (Maybe DataCon)  lookupIntegerSDataConName dflags hsc_env = case cIntegerLibraryType of      IntegerGMP -> guardIntegerUse dflags $ liftM (Just . tyThingDataCon) $                    lookupGlobal hsc_env integerSDataConName      IntegerSimple -> return Nothing --- | Helper for 'lookupMkIntegerName' and 'lookupIntegerSDataConName' +lookupNaturalSDataConName :: DynFlags -> HscEnv -> IO (Maybe DataCon) +lookupNaturalSDataConName dflags hsc_env = case cIntegerLibraryType of +    IntegerGMP -> guardNaturalUse dflags $ liftM (Just . tyThingDataCon) $ +                  lookupGlobal hsc_env naturalSDataConName +    IntegerSimple -> return Nothing + +-- | Helper for 'lookupMkIntegerName', 'lookupIntegerSDataConName'  guardIntegerUse :: DynFlags -> IO a -> IO a  guardIntegerUse dflags act    | thisPackage dflags == primUnitId @@ -1521,15 +1558,33 @@ guardIntegerUse dflags act    = return $ panic "Can't use Integer in integer-*"    | otherwise = act +-- | Helper for 'lookupMkNaturalName', 'lookupNaturalSDataConName' +-- +-- Just like we can't use Integer literals in `integer-*`, we can't use Natural +-- literals in `base`. If we do, we get interface loading error for GHC.Natural. +guardNaturalUse :: DynFlags -> IO a -> IO a +guardNaturalUse dflags act +  | thisPackage dflags == primUnitId +  = return $ panic "Can't use Natural in ghc-prim" +  | thisPackage dflags == integerUnitId +  = return $ panic "Can't use Natural in integer-*" +  | thisPackage dflags == baseUnitId +  = return $ panic "Can't use Natural in base" +  | otherwise = act +  mkInitialCorePrepEnv :: DynFlags -> HscEnv -> IO CorePrepEnv  mkInitialCorePrepEnv dflags hsc_env      = do mkIntegerId <- lookupMkIntegerName dflags hsc_env +         mkNaturalId <- lookupMkNaturalName dflags hsc_env           integerSDataCon <- lookupIntegerSDataConName dflags hsc_env +         naturalSDataCon <- lookupNaturalSDataConName dflags hsc_env           return $ CPE {                        cpe_dynFlags = dflags,                        cpe_env = emptyVarEnv,                        cpe_mkIntegerId = mkIntegerId, -                      cpe_integerSDataCon = integerSDataCon +                      cpe_mkNaturalId = mkNaturalId, +                      cpe_integerSDataCon = integerSDataCon, +                      cpe_naturalSDataCon = naturalSDataCon                    }  extendCorePrepEnv :: CorePrepEnv -> Id -> Id -> CorePrepEnv @@ -1554,6 +1609,9 @@ lookupCorePrepEnv cpe id  getMkIntegerId :: CorePrepEnv -> Id  getMkIntegerId = cpe_mkIntegerId +getMkNaturalId :: CorePrepEnv -> Id +getMkNaturalId = cpe_mkNaturalId +  ------------------------------------------------------------------------------  -- Cloning binders  -- --------------------------------------------------------------------------- diff --git a/compiler/coreSyn/CoreUnfold.hs b/compiler/coreSyn/CoreUnfold.hs index 3d26d3c721..7bd512d98f 100644 --- a/compiler/coreSyn/CoreUnfold.hs +++ b/compiler/coreSyn/CoreUnfold.hs @@ -701,7 +701,8 @@ sizeExpr dflags bOMB_OUT_SIZE top_args expr  -- | Finds a nominal size of a string literal.  litSize :: Literal -> Int  -- Used by CoreUnfold.sizeExpr -litSize (LitInteger {}) = 100   -- Note [Size of literal integers] +litSize (LitNumber LitNumInteger _ _) = 100   -- Note [Size of literal integers] +litSize (LitNumber LitNumNatural _ _) = 100  litSize (MachStr str)   = 10 + 10 * ((BS.length str + 3) `div` 4)          -- If size could be 0 then @f "x"@ might be too small          -- [Sept03: make literal strings a bit bigger to avoid fruitless diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index 88e1f7167e..8f4f84b550 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -2409,12 +2409,13 @@ and 'execute' it rather than allocating it statically.  -- | This function is called only on *top-level* right-hand sides.  -- Returns @True@ if the RHS can be allocated statically in the output,  -- with no thunks involved at all. -rhsIsStatic :: Platform -            -> (Name -> Bool)         -- Which names are dynamic -            -> (Integer -> CoreExpr)  -- Desugaring for integer literals (disgusting) -                                      -- C.f. Note [Disgusting computation of CafRefs] -                                      --      in TidyPgm -            -> CoreExpr -> Bool +rhsIsStatic +   :: Platform +   -> (Name -> Bool)         -- Which names are dynamic +   -> (LitNumType -> Integer -> Maybe CoreExpr) +      -- Desugaring for some literals (disgusting) +      -- C.f. Note [Disgusting computation of CafRefs] in TidyPgm +   -> CoreExpr -> Bool  -- It's called (i) in TidyPgm.hasCafRefs to decide if the rhs is, or  -- refers to, CAFs; (ii) in CoreToStg to decide whether to put an  -- update flag on it and (iii) in DsExpr to decide how to expand @@ -2469,7 +2470,7 @@ rhsIsStatic :: Platform  --  --    c) don't look through unfolding of f in (f x). -rhsIsStatic platform is_dynamic_name cvt_integer rhs = is_static False rhs +rhsIsStatic platform is_dynamic_name cvt_literal rhs = is_static False rhs    where    is_static :: Bool     -- True <=> in a constructor argument; must be atomic              -> CoreExpr -> Bool @@ -2479,7 +2480,9 @@ rhsIsStatic platform is_dynamic_name cvt_integer rhs = is_static False rhs                                                && is_static in_arg e    is_static in_arg (Cast e _)             = is_static in_arg e    is_static _      (Coercion {})          = True   -- Behaves just like a literal -  is_static in_arg (Lit (LitInteger i _)) = is_static in_arg (cvt_integer i) +  is_static in_arg (Lit (LitNumber nt i _)) = case cvt_literal nt i of +    Just e  -> is_static in_arg e +    Nothing -> True    is_static _      (Lit (MachLabel {}))   = False    is_static _      (Lit _)                = True          -- A MachLabel (foreign import "&foo") in an argument diff --git a/compiler/coreSyn/MkCore.hs b/compiler/coreSyn/MkCore.hs index aad6d14a90..ef9da21e9a 100644 --- a/compiler/coreSyn/MkCore.hs +++ b/compiler/coreSyn/MkCore.hs @@ -260,13 +260,9 @@ mkIntegerExpr i = do t <- lookupTyCon integerTyConName                       return (Lit (mkLitInteger i (mkTyConTy t)))  -- | Create a 'CoreExpr' which will evaluate to the given @Natural@ --- --- TODO: should we add LitNatural to Core? -mkNaturalExpr  :: MonadThings m => Integer -> m CoreExpr  -- Result :: Natural -mkNaturalExpr i = do iExpr <- mkIntegerExpr i -                     fiExpr <- lookupId naturalFromIntegerName -                     return (mkCoreApps (Var fiExpr) [iExpr]) - +mkNaturalExpr  :: MonadThings m => Integer -> m CoreExpr +mkNaturalExpr i = do t <- lookupTyCon naturalTyConName +                     return (Lit (mkLitNatural i (mkTyConTy t)))  -- | Create a 'CoreExpr' which will evaluate to the given @Float@  mkFloatExpr :: Float -> CoreExpr | 
