Skip to content
GitLab
Projects
Groups
Snippets
/
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Glasgow Haskell Compiler
GHC
Commits
fd6ccd02
Commit
fd6ccd02
authored
Jan 11, 2007
by
simonpj@microsoft.com
Browse files
Fix a nasty recursive loop in typechecking interface files
parent
8ff14137
Changes
3
Hide whitespace changes
Inline
Side-by-side
compiler/iface/BuildTyCl.lhs
View file @
fd6ccd02
...
...
@@ -115,15 +115,15 @@ mkNewTyConRhs :: Name -> TyCon -> DataCon -> TcRnIf m n AlgTyConRhs
-- because the latter is part of a knot, whereas the former is not.
mkNewTyConRhs tycon_name tycon con
= do { co_tycon_name <- newImplicitBinder tycon_name mkNewTyCoOcc
; let co_tycon = mkNewTypeCoercion co_tycon_name tycon etad_rhs
; let co_tycon = mkNewTypeCoercion co_tycon_name tycon
etad_tvs
etad_rhs
cocon_maybe | all_coercions || isRecursiveTyCon tycon
= Just co_tycon
| otherwise
= Nothing
; return (NewTyCon { data_con = con,
nt_rhs = rhs_ty,
nt_etad_rhs = etad_rhs,
nt_co = cocon_maybe,
nt_etad_rhs =
(etad_tvs,
etad_rhs
)
,
nt_co
= cocon_maybe,
-- Coreview looks through newtypes with a Nothing
-- for nt_co, or uses explicit coercions otherwise
nt_rep = mkNewTyConRep tycon rhs_ty }) }
...
...
@@ -137,8 +137,10 @@ mkNewTyConRhs tycon_name tycon con
-- Instantiate the data con with the
-- type variables from the tycon
etad_rhs :: ([TyVar], Type)
etad_rhs = eta_reduce (reverse tvs) rhs_ty
etad_tvs :: [TyVar] -- Matched lazily, so that mkNewTypeCoercion can
etad_rhs :: Type -- return a TyCon without pulling on rhs_ty
-- See Note [Tricky iface loop] in LoadIface
(etad_tvs, etad_rhs) = eta_reduce (reverse tvs) rhs_ty
eta_reduce :: [TyVar] -- Reversed
-> Type -- Rhs type
...
...
@@ -300,7 +302,7 @@ buildClass class_name tvs sc_theta fds ats sig_stuff tc_isrec
; let { clas_kind = mkArrowKinds (map tyVarKind tvs) liftedTypeKind
; tycon = mkClassTyCon tycon_name clas_kind tvs
rhs rec_clas tc_isrec
rhs rec_clas tc_isrec
-- A class can be recursive, and in the case of newtypes
-- this matters. For example
-- class C a where { op :: C b => a -> b -> Int }
...
...
compiler/iface/LoadIface.lhs
View file @
fd6ccd02
...
...
@@ -323,7 +323,27 @@ loadDecl ignore_prags mod (_version, decl)
; thing <- forkM doc $ do { bumpDeclStats main_name
; tcIfaceDecl ignore_prags decl }
-- Populate the type environment with the implicitTyThings too
-- Populate the type environment with the implicitTyThings too.
--
-- Note [Tricky iface loop]
-- ~~~~~~~~~~~~~~~~~~~~~~~~
-- The delicate point here is that 'mini-env' should be
-- buildable from 'thing' without demanding any of the things 'forkM'd
-- by tcIfaceDecl. For example
-- class C a where { data T a; op :: T a -> Int }
-- We return the bindings
-- [("C", <cls>), ("T", lookup env "T"), ("op", lookup env "op")]
-- The call (lookup env "T") must return the tycon T without first demanding
-- op; because getting the latter will look up T, hence loop.
--
-- Of course, there is no reason in principle why (lookup env "T") should demand
-- anything do to with op, but take care:
-- (a) implicitTyThings, and
-- (b) getOccName of all the things returned by implicitThings,
-- must not depend on any of the nested type-checks
--
-- All a bit too finely-balanced for my liking.
; let mini_env = mkOccEnv [(getOccName t, t) | t <- implicitTyThings thing]
lookup n = case lookupOccEnv mini_env (getOccName n) of
Just thing -> thing
...
...
compiler/types/Coercion.lhs
View file @
fd6ccd02
...
...
@@ -275,8 +275,8 @@ mkUnsafeCoercion ty1 ty2
-- See note [Newtype coercions] in TyCon
mkNewTypeCoercion :: Name -> TyCon ->
(
[TyVar]
,
Type
)
-> TyCon
mkNewTypeCoercion name tycon
(
tvs
,
rhs_ty
)
mkNewTypeCoercion :: Name -> TyCon -> [TyVar]
->
Type -> TyCon
mkNewTypeCoercion name tycon tvs rhs_ty
= mkCoercionTyCon name co_con_arity rule
where
co_con_arity = length tvs
...
...
Write
Preview
Supports
Markdown
0%
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!
Cancel
Please
register
or
sign in
to comment