Skip to content
GitLab
Projects
Groups
Snippets
Help
Loading...
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
GHC
Project overview
Project overview
Details
Activity
Releases
Repository
Repository
Files
Commits
Branches
Tags
Contributors
Graph
Compare
Locked Files
Issues
0
Issues
0
List
Boards
Labels
Service Desk
Milestones
Iterations
Merge Requests
0
Merge Requests
0
Requirements
Requirements
List
CI / CD
CI / CD
Pipelines
Jobs
Schedules
Security & Compliance
Security & Compliance
Dependency List
License Compliance
Operations
Operations
Incidents
Environments
Packages & Registries
Packages & Registries
Package Registry
Container Registry
Analytics
Analytics
CI / CD
Code Review
Insights
Issue
Repository
Value Stream
Wiki
Wiki
Snippets
Snippets
Members
Members
Collapse sidebar
Close sidebar
Activity
Graph
Create a new issue
Jobs
Commits
Issue Boards
Open sidebar
Alex D
GHC
Commits
491b818a
Commit
491b818a
authored
Nov 26, 2010
by
simonpj@microsoft.com
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
Tidy up the handling of wild-card binders, and make Lint check it
See Note [WildCard binders] in SimplEnv. Spotted by Roman.
parent
30c17e70
Changes
4
Hide whitespace changes
Inline
Side-by-side
Showing
4 changed files
with
39 additions
and
11 deletions
+39
-11
compiler/coreSyn/CoreLint.lhs
compiler/coreSyn/CoreLint.lhs
+5
-1
compiler/coreSyn/MkCore.lhs
compiler/coreSyn/MkCore.lhs
+2
-2
compiler/prelude/PrelNames.lhs
compiler/prelude/PrelNames.lhs
+7
-3
compiler/simplCore/SimplEnv.lhs
compiler/simplCore/SimplEnv.lhs
+25
-5
No files found.
compiler/coreSyn/CoreLint.lhs
View file @
491b818a
...
...
@@ -227,7 +227,11 @@ lintCoreExpr (Var var)
= do { checkL (not (var == oneTupleDataConId))
(ptext (sLit "Illegal one-tuple"))
; checkDeadIdOcc var
; checkL (not (var `hasKey` wildCardKey))
(ptext (sLit "Occurence of a wild-card binder") <+> ppr var)
-- See Note [WildCard binders] in SimplEnv
; checkDeadIdOcc var
; var' <- lookupIdInScope var
; return (idType var') }
...
...
compiler/coreSyn/MkCore.lhs
View file @
491b818a
...
...
@@ -65,7 +65,6 @@ import Name
import Outputable
import FastString
import UniqSupply
import Unique ( mkBuiltinUnique )
import BasicTypes
import Util ( notNull, zipEqual )
import Constants
...
...
@@ -156,8 +155,9 @@ mkWildEvBinder pred = mkWildValBinder (mkPredTy pred)
-- that you expect to use only at a *binding* site. Do not use it at
-- occurrence sites because it has a single, fixed unique, and it's very
-- easy to get into difficulties with shadowing. That's why it is used so little.
-- See Note [WildCard binders] in SimplEnv
mkWildValBinder :: Type -> Id
mkWildValBinder ty = mk
SysLocal (fsLit "wild") (mkBuiltinUnique 1)
ty
mkWildValBinder ty = mk
LocalId wildCardName
ty
mkWildCase :: CoreExpr -> Type -> Type -> [CoreAlt] -> CoreExpr
-- Make a case expression whose case binder is unused
...
...
compiler/prelude/PrelNames.lhs
View file @
491b818a
...
...
@@ -58,7 +58,7 @@ import Unique ( Unique, Uniquable(..), hasKey,
mkTupleTyConUnique
)
import BasicTypes ( Boxity(..), Arity )
import Name
( Name, mkInternalName, mkExternal
Name )
import Name
( Name, mkInternalName, mkExternalName, mkSystemVar
Name )
import SrcLoc
import FastString
\end{code}
...
...
@@ -542,6 +542,9 @@ and it's convenient to write them all down in one place.
\begin{code}
wildCardName :: Name
wildCardName = mkSystemVarName wildCardKey (fsLit "wild")
runMainIOName :: Name
runMainIOName = varQual gHC_TOP_HANDLER (fsLit "runMainIO") runMainKey
...
...
@@ -1127,10 +1130,11 @@ absentErrorIdKey, augmentIdKey, appendIdKey, buildIdKey, errorIdKey,
noMethodBindingErrorIdKey, nonExhaustiveGuardsErrorIdKey,
runtimeErrorIdKey, parErrorIdKey, parIdKey, patErrorIdKey,
realWorldPrimIdKey, recConErrorIdKey, recUpdErrorIdKey,
traceIdKey,
traceIdKey,
wildCardKey,
unpackCStringUtf8IdKey, unpackCStringAppendIdKey,
unpackCStringFoldrIdKey, unpackCStringIdKey :: Unique
absentErrorIdKey = mkPreludeMiscIdUnique 1
wildCardKey = mkPreludeMiscIdUnique 0 -- See Note [WildCard]
absentErrorIdKey = mkPreludeMiscIdUnique 1
augmentIdKey = mkPreludeMiscIdUnique 3
appendIdKey = mkPreludeMiscIdUnique 4
buildIdKey = mkPreludeMiscIdUnique 5
...
...
compiler/simplCore/SimplEnv.lhs
View file @
491b818a
...
...
@@ -46,6 +46,8 @@ import VarEnv
import VarSet
import OrdList
import Id
import MkCore
import TysWiredIn
import qualified CoreSubst
import qualified Type ( substTy, substTyVarBndr, substTyVar )
import Type hiding ( substTy, substTyVarBndr, substTyVar )
...
...
@@ -220,13 +222,31 @@ seIdSubst:
\begin{code}
mkSimplEnv :: SimplifierMode -> SimplEnv
mkSimplEnv mode
= SimplEnv { seCC = subsumedCCS,
seMode = mode, seInScope = emptyInScopeSet,
seFloats = emptyFloats,
seTvSubst = emptyVarEnv, seIdSubst = emptyVarEnv }
= SimplEnv { seCC = subsumedCCS
, seMode = mode
, seInScope = init_in_scope
, seFloats = emptyFloats
, seTvSubst = emptyVarEnv
, seIdSubst = emptyVarEnv }
-- The top level "enclosing CC" is "SUBSUMED".
---------------------
init_in_scope :: InScopeSet
init_in_scope = mkInScopeSet (unitVarSet (mkWildValBinder unitTy))
-- See Note [WildCard binders]
\end{code}
Note [WildCard binders]
~~~~~~~~~~~~~~~~~~~~~~~
The program to be simplified may have wild binders
case e of wild { p -> ... }
We want to *rename* them away, so that there are no
occurrences of 'wild' (with wildCardKey). The easy
way to do that is to start of with a representative
Id in the in-scope set
There should be no *occurrences* of wild.
\begin{code}
getMode :: SimplEnv -> SimplifierMode
getMode env = seMode env
...
...
Write
Preview
Markdown
is supported
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment