summaryrefslogtreecommitdiff
path: root/ghc/compiler/coreSyn/CoreSyn.lhs
diff options
context:
space:
mode:
authorsimonpj <unknown>2001-05-25 08:55:04 +0000
committersimonpj <unknown>2001-05-25 08:55:04 +0000
commit3af411e913102d8ec1234f32abe99374f077e3f7 (patch)
tree78f2437f05d08a64f6f506bef866bbe4d10c29d3 /ghc/compiler/coreSyn/CoreSyn.lhs
parent86cdf87a1ed26801e3889ca5ba819e565fb47aac (diff)
downloadhaskell-3af411e913102d8ec1234f32abe99374f077e3f7.tar.gz
[project @ 2001-05-25 08:55:03 by simonpj]
------------------------------------- Wibbles to Don's runtime-types commit ------------------------------------- There was an upside down predicate which utterly broke the compiler. While I was about it * I changed the global flag to opt_RuntimeTypes with command line option -fruntime-types (was -fkeep-stg-types) * I moved isRuntimeArg, isRuntimeVar to CoreSyn
Diffstat (limited to 'ghc/compiler/coreSyn/CoreSyn.lhs')
-rw-r--r--ghc/compiler/coreSyn/CoreSyn.lhs19
1 files changed, 18 insertions, 1 deletions
diff --git a/ghc/compiler/coreSyn/CoreSyn.lhs b/ghc/compiler/coreSyn/CoreSyn.lhs
index a69c239b21..10ffe27d53 100644
--- a/ghc/compiler/coreSyn/CoreSyn.lhs
+++ b/ghc/compiler/coreSyn/CoreSyn.lhs
@@ -22,7 +22,7 @@ module CoreSyn (
coreExprCc,
flattenBinds,
- isValArg, isTypeArg, valArgCount, valBndrCount,
+ isValArg, isTypeArg, valArgCount, valBndrCount, isRuntimeArg, isRuntimeVar,
-- Unfoldings
Unfolding(..), UnfoldingGuidance(..), -- Both abstract everywhere but in CoreUnfold.lhs
@@ -49,6 +49,7 @@ module CoreSyn (
#include "HsVersions.h"
+import CmdLineOpts ( opt_RuntimeTypes )
import CostCentre ( CostCentre, noCostCentre )
import Var ( Var, Id, TyVar, isTyVar, isId )
import Type ( Type, mkTyVarTy, seqType )
@@ -490,6 +491,22 @@ coreExprCc other = noCostCentre
%* *
%************************************************************************
+@isRuntimeVar v@ returns if (Lam v _) really becomes a lambda at runtime,
+i.e. if type applications are actual lambdas because types are kept around
+at runtime.
+
+Similarly isRuntimeArg.
+
+\begin{code}
+isRuntimeVar :: Var -> Bool
+isRuntimeVar | opt_RuntimeTypes = \v -> True
+ | otherwise = \v -> isId v
+
+isRuntimeArg :: CoreExpr -> Bool
+isRuntimeArg | opt_RuntimeTypes = \e -> True
+ | otherwise = \e -> isValArg e
+\end{code}
+
\begin{code}
isValArg (Type _) = False
isValArg other = True