summaryrefslogtreecommitdiff
path: root/compiler/coreSyn/CorePrep.hs
diff options
context:
space:
mode:
authorSylvain Henry <hsyl20@gmail.com>2018-06-15 16:23:53 -0400
committerBen Gamari <ben@smart-cactus.org>2018-06-15 16:23:54 -0400
commitfe770c211631e7b4c9b0b1e88ef9b6046c6585ef (patch)
treee6a061a92d8d0d71d40c699982ee471627d816e0 /compiler/coreSyn/CorePrep.hs
parent42f3b53b5bc4674e41f16de08094821fe1aaec00 (diff)
downloadhaskell-fe770c211631e7b4c9b0b1e88ef9b6046c6585ef.tar.gz
Built-in Natural literals in Core
Add support for built-in Natural literals in Core. - Replace MachInt,MachWord, LitInteger, etc. with a single LitNumber constructor with a LitNumType field - Support built-in Natural literals - Add desugar warning for negative literals - Move Maybe(..) from GHC.Base to GHC.Maybe for module dependency reasons This patch introduces only a few rules for Natural literals (compared to Integer's rules). Factorization of the built-in rules for numeric literals will be done in another patch as this one is already big to review. Test Plan: validate test build with integer-simple Reviewers: hvr, bgamari, goldfire, Bodigrim, simonmar Reviewed By: bgamari Subscribers: phadej, simonpj, RyanGlScott, carter, hsyl20, rwbarton, thomie GHC Trac Issues: #14170, #14465 Differential Revision: https://phabricator.haskell.org/D4212
Diffstat (limited to 'compiler/coreSyn/CorePrep.hs')
-rw-r--r--compiler/coreSyn/CorePrep.hs76
1 files changed, 67 insertions, 9 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
-- ---------------------------------------------------------------------------