Skip to content
GitLab
Explore
Sign in
Register
Primary navigation
Search or go to…
Project
GHC
Manage
Activity
Members
Labels
Plan
Issues
Issue boards
Milestones
Wiki
Requirements
Code
Merge requests
Repository
Branches
Commits
Tags
Repository graph
Compare revisions
Snippets
Locked files
Build
Pipelines
Jobs
Pipeline schedules
Test cases
Artifacts
Deploy
Releases
Package Registry
Container Registry
Model registry
Operate
Environments
Terraform modules
Monitor
Incidents
Analyze
Value stream analytics
Contributor analytics
CI/CD analytics
Repository analytics
Code review analytics
Issue analytics
Insights
Model experiments
Help
Help
Support
GitLab documentation
Compare GitLab plans
Community forum
Contribute to GitLab
Provide feedback
Terms and privacy
Keyboard shortcuts
?
Snippets
Groups
Projects
Show more breadcrumbs
Javier Neira
GHC
Commits
4496fda2
Commit
4496fda2
authored
12 years ago
by
Simon Peyton Jones
Browse files
Options
Downloads
Patches
Plain Diff
Minor refactoring plus comments
parent
5a6a223f
Loading
Loading
No related merge requests found
Changes
2
Hide whitespace changes
Inline
Side-by-side
Showing
2 changed files
compiler/typecheck/TcMType.lhs
+13
-11
13 additions, 11 deletions
compiler/typecheck/TcMType.lhs
compiler/typecheck/TcTyClsDecls.lhs
+6
-6
6 additions, 6 deletions
compiler/typecheck/TcTyClsDecls.lhs
with
19 additions
and
17 deletions
compiler/typecheck/TcMType.lhs
+
13
−
11
View file @
4496fda2
...
...
@@ -542,21 +542,23 @@ zonkQuantifiedTyVars :: [TcTyVar] -> TcM [TcTyVar]
-- A kind variable k may occur *after* a tyvar mentioning k in its kind
zonkQuantifiedTyVars tyvars
= do { let (kvs, tvs) = partition isKindVar tyvars
; poly_kinds <- xoptM Opt_PolyKinds
; if poly_kinds then
mapM zonkQuantifiedTyVar (kvs ++ tvs)
-- Because of the order, any kind variables
-- mentioned in the kinds of the type variables refer to
-- the now-quantified versions
else
(meta_kvs, skolem_kvs) = partition isMetaTyVar kvs
-- In the non-PolyKinds case, default the kind variables
-- to *, and zonk the tyvars as usual. Notice that this
-- may make zonkQuantifiedTyVars return a shorter list
-- than it was passed, but that's ok
do { let (meta_kvs, skolem_kvs) = partition isMetaTyVar kvs
; WARN ( not (null skolem_kvs), ppr skolem_kvs )
mapM_ defaultKindVarToStar meta_kvs
; mapM zonkQuantifiedTyVar (skolem_kvs ++ tvs) } }
; poly_kinds <- xoptM Opt_PolyKinds
; qkvs <- if poly_kinds
then return kvs
else WARN ( not (null skolem_kvs), ppr skolem_kvs )
do { mapM_ defaultKindVarToStar meta_kvs
; return skolem_kvs } -- Should be empty
; mapM zonkQuantifiedTyVar (qkvs ++ tvs) }
-- Because of the order, any kind variables
-- mentioned in the kinds of the type variables refer to
-- the now-quantified versions
zonkQuantifiedTyVar :: TcTyVar -> TcM TcTyVar
-- The quantified type variables often include meta type variables
...
...
This diff is collapsed.
Click to expand it.
compiler/typecheck/TcTyClsDecls.lhs
+
6
−
6
View file @
4496fda2
...
...
@@ -900,11 +900,11 @@ tcFamTyPats fam_tc (HsWB { hswb_cts = arg_pats, hswb_kvs = kvars, hswb_tvs = tva
; tcHsArgTys (quotes (ppr fam_tc)) arg_pats arg_kinds }
; let all_args = fam_arg_kinds ++ typats
-- Find free variables (after zonking)
; tkvs <- zonkTyVarsAndFV (tyVarsOfTypes all_args)
-- Turn them into skolems, so that we don't subsequently
-- Find free variables (after zonking) and turn
-- them into skolems, so that we don't subsequently
-- replace a meta kind var with AnyK
-- Very like kindGeneralize
; tkvs <- zonkTyVarsAndFV (tyVarsOfTypes all_args)
; qtkvs <- zonkQuantifiedTyVars (varSetElems tkvs)
-- Zonk the patterns etc into the Type world
...
...
@@ -912,7 +912,7 @@ tcFamTyPats fam_tc (HsWB { hswb_cts = arg_pats, hswb_kvs = kvars, hswb_tvs = tva
; all_args' <- zonkTcTypeToTypes ze all_args
; res_kind' <- zonkTcTypeToType ze res_kind
; traceTc "tcFamPats" (pprTvBndrs qtkvs' $$ ppr all_args' $$ ppr res_kind')
; traceTc "tcFam
Ty
Pats" (pprTvBndrs qtkvs' $$ ppr all_args' $$ ppr res_kind')
; tcExtendTyVarEnv qtkvs' $
thing_inside qtkvs' all_args' res_kind' }
\end{code}
...
...
@@ -1070,7 +1070,7 @@ tcConDecl new_or_data rep_tycon res_tmpl -- Data types
-- free kind variables of the type, for kindGeneralize to work on
-- Generalise the kind variables (returning quantifed TcKindVars)
-- and quanify the type variables (substiting their kinds)
-- and quan
t
ify the type variables (substiting their kinds)
; kvs <- kindGeneralize (tyVarsOfType pretend_con_ty) (map getName tvs)
; tvs <- zonkQuantifiedTyVars tvs
...
...
This diff is collapsed.
Click to expand it.
Preview
0%
Loading
Try again
or
attach a new file
.
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Save comment
Cancel
Please
register
or
sign in
to comment