Skip to content
GitLab
Menu
Projects
Groups
Snippets
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Alex D
GHC
Commits
b8c98e4e
Commit
b8c98e4e
authored
Sep 06, 2006
by
simonpj@microsoft.com
Browse files
Improve error reporting for SigTvs, and add comments
parent
39fd94e2
Changes
3
Hide whitespace changes
Inline
Side-by-side
compiler/typecheck/TcBinds.lhs
View file @
b8c98e4e
...
...
@@ -1041,9 +1041,15 @@ tcInstSig_maybe sig_fn name
tcInstSig :: Bool -> Name -> [Name] -> TcM TcSigInfo
-- Instantiate the signature, with either skolems or meta-type variables
-- depending on the use_skols boolean
-- depending on the use_skols boolean. This variable is set True
-- when we are typechecking a single function binding; and False for
-- pattern bindigs and a group of several function bindings.
-- Reason: in the latter cases, the "skolems" can be unified together,
-- so they aren't properly rigid in the type-refinement sense.
-- NB: unless we are doing H98, each function with a sig will be done
-- separately, even if it's mutually recursive, so use_skols will be True
--
-- We always instantiate with fresh
s
uniques,
-- We always instantiate with fresh uniques,
-- although we keep the same print-name
--
-- type T = forall a. [a] -> [a]
...
...
compiler/typecheck/TcType.lhs
View file @
b8c98e4e
...
...
@@ -284,14 +284,14 @@ The trouble is that the occurrences of z in the RHS force a* and b* to
be the *same*, so we can't make them into skolem constants that don't unify
with each other. Alas.
On the other hand, we *must* use skolems for signature type variables,
becuase GADT type refinement refines skolems only.
One solution would be insist that in the above defn the programmer uses
the same type variable in both type signatures. But that takes explanation.
The alternative (currently implemented) is to have a special kind of skolem
constant, SigSkokTv, which can unify with other SigSkolTvs.
constant, SigTv, which can unify with other SigTvs. These are *not* treated
as righd for the purposes of GADTs. And they are used *only* for pattern
bindings and mutually recursive function bindings. See the function
TcBinds.tcInstSig, and its use_skols parameter.
\begin{code}
...
...
@@ -420,15 +420,23 @@ pprUserTypeCtxt SpecInstCtxt = ptext SLIT("a SPECIALISE instance pragma")
tidySkolemTyVar :: TidyEnv -> TcTyVar -> (TidyEnv, TcTyVar)
-- Tidy the type inside a GenSkol, preparatory to printing it
tidySkolemTyVar env tv
= ASSERT( isSkolemTyVar tv )
= ASSERT( isSkolemTyVar tv
|| isSigTyVar tv
)
(env1, mkTcTyVar (tyVarName tv) (tyVarKind tv) info1)
where
(env1, info1) = case tcTyVarDetails tv of
SkolemTv (GenSkol tvs ty loc) -> (env2, SkolemTv (GenSkol tvs1 ty1 loc))
SkolemTv info -> (env1, SkolemTv info')
where
(env1, info') = tidy_skol_info env info
MetaTv (SigTv info) box -> (env1, MetaTv (SigTv info') box)
where
(env1, info') = tidy_skol_info env info
info -> (env, info)
tidy_skol_info env (GenSkol tvs ty loc) = (env2, GenSkol tvs1 ty1 loc)
where
(env1, tvs1) = tidyOpenTyVars env tvs
(env2, ty1) = tidyOpenType env1 ty
info
->
(env, info)
tidy_skol_info env
info
=
(env, info)
pprSkolTvBinding :: TcTyVar -> SDoc
-- Print info about the binding of a skolem tyvar,
...
...
compiler/typecheck/TcUnify.lhs
View file @
b8c98e4e
...
...
@@ -48,9 +48,9 @@ import TcType ( TcKind, TcType, TcTyVar, BoxyTyVar, TcTauType,
tcSplitForAllTys, tcSplitAppTy_maybe, tcSplitFunTys, mkTyVarTys,
tcSplitSigmaTy, tyVarsOfType, mkPhiTy, mkTyVarTy, mkPredTy,
typeKind, mkForAllTys, mkAppTy, isBoxyTyVar,
exactTyVarsOfType,
tcView,
exactTyVarsOfType,
tidyOpenType, tidyOpenTyVar, tidyOpenTyVars,
pprType, tidyKind, tidySkolemTyVar, isSkolemTyVar,
tcView,
pprType, tidyKind, tidySkolemTyVar, isSkolemTyVar,
isSigTyVar,
TvSubst, mkTvSubst, zipTyEnv, zipOpenTvSubst, emptyTvSubst,
substTy, substTheta,
lookupTyVar, extendTvSubst )
...
...
@@ -1501,8 +1501,8 @@ ppr_ty env ty
simple_result = (env1, quotes (ppr tidy_ty), empty)
; case tidy_ty of
TyVarTy tv
| isSkolemTyVar tv
-> return (env2, pp_rigid
tv
',
pprSkolTvBinding tv')
| isSkolemTyVar tv
|| isSigTyVar
tv
-> return (env2, pp_rigid tv',
pprSkolTvBinding tv')
| otherwise -> return simple_result
where
(env2, tv') = tidySkolemTyVar env1 tv
...
...
Write
Preview
Supports
Markdown
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