summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSimon Peyton Jones <simonpj@microsoft.com>2016-01-15 17:30:30 +0000
committerSimon Peyton Jones <simonpj@microsoft.com>2016-01-18 11:55:41 +0000
commitec8a188a927a4db2e709541765e5ef545eae284c (patch)
treecbde55cf4ee60e4265536aee730c7c41d668824e
parent6e0c0fd2e09c552bf38e22645347dbb2e7327e8e (diff)
downloadhaskell-ec8a188a927a4db2e709541765e5ef545eae284c.tar.gz
Refactoring on IdInfo and system derived names
Some modest refactoring, triggered in part by Trac #11051 * Kill off PatSynId, ReflectionId in IdDetails They were barely used, and only for pretty-printing * Add helper function Id.mkExportedVanillaId, and use it * Polish up OccName.isDerivedOccName, as a predicate for definitions generated internally by GHC, which we might not want to show to the user. * Kill off unused OccName.mkDerivedTyConOcc * Shorten the derived OccNames for newtype and data instance axioms * A bit of related refactoring around newFamInstAxiomName
-rw-r--r--compiler/basicTypes/Id.hs6
-rw-r--r--compiler/basicTypes/IdInfo.hs13
-rw-r--r--compiler/basicTypes/OccName.hs23
-rw-r--r--compiler/deSugar/DsExpr.hs3
-rw-r--r--compiler/iface/MkIface.hs5
-rw-r--r--compiler/typecheck/TcEnv.hs9
-rw-r--r--compiler/typecheck/TcInstDcls.hs5
-rw-r--r--compiler/typecheck/TcRnDriver.hs13
-rw-r--r--compiler/typecheck/TcTyClsDecls.hs51
-rw-r--r--compiler/typecheck/TcTyDecls.hs2
-rw-r--r--compiler/typecheck/TcTypeable.hs7
-rw-r--r--testsuite/tests/deSugar/should_compile/T2431.stderr6
-rw-r--r--testsuite/tests/ghci/scripts/T4175.stdout22
-rw-r--r--testsuite/tests/ghci/scripts/T7939.stdout2
-rw-r--r--testsuite/tests/indexed-types/should_compile/T3017.stderr7
-rw-r--r--testsuite/tests/numeric/should_compile/T7116.stdout2
-rw-r--r--testsuite/tests/partial-sigs/should_compile/ADT.stderr3
-rw-r--r--testsuite/tests/partial-sigs/should_compile/DataFamilyInstanceLHS.stderr14
-rw-r--r--testsuite/tests/partial-sigs/should_compile/NamedWildcardInDataFamilyInstanceLHS.stderr14
-rw-r--r--testsuite/tests/partial-sigs/should_compile/NamedWildcardInTypeFamilyInstanceLHS.stderr6
-rw-r--r--testsuite/tests/partial-sigs/should_compile/SkipMany.stderr4
-rw-r--r--testsuite/tests/partial-sigs/should_compile/TypeFamilyInstanceLHS.stderr6
-rw-r--r--testsuite/tests/roles/should_compile/Roles1.stderr9
-rw-r--r--testsuite/tests/roles/should_compile/Roles13.stderr28
-rw-r--r--testsuite/tests/roles/should_compile/Roles14.stderr17
-rw-r--r--testsuite/tests/roles/should_compile/Roles2.stderr24
-rw-r--r--testsuite/tests/roles/should_compile/Roles3.stderr62
-rw-r--r--testsuite/tests/roles/should_compile/Roles4.stderr32
-rw-r--r--testsuite/tests/roles/should_compile/T8958.stderr45
-rw-r--r--testsuite/tests/simplCore/should_compile/T3717.stderr2
-rw-r--r--testsuite/tests/simplCore/should_compile/T3772.stdout2
-rw-r--r--testsuite/tests/simplCore/should_compile/T4201.stdout2
-rw-r--r--testsuite/tests/simplCore/should_compile/T4908.stderr2
-rw-r--r--testsuite/tests/simplCore/should_compile/T4930.stderr2
-rw-r--r--testsuite/tests/simplCore/should_compile/T7360.stderr10
-rw-r--r--testsuite/tests/simplCore/should_compile/T9400.stderr2
-rw-r--r--testsuite/tests/simplCore/should_compile/spec-inline.stderr2
-rw-r--r--testsuite/tests/typecheck/should_compile/tc231.stderr8
38 files changed, 288 insertions, 184 deletions
diff --git a/compiler/basicTypes/Id.hs b/compiler/basicTypes/Id.hs
index 775a77ba38..b273b66256 100644
--- a/compiler/basicTypes/Id.hs
+++ b/compiler/basicTypes/Id.hs
@@ -32,7 +32,7 @@ module Id (
mkGlobalId, mkVanillaGlobal, mkVanillaGlobalWithInfo,
mkLocalId, mkLocalCoVar, mkLocalIdOrCoVar,
mkLocalIdOrCoVarWithInfo,
- mkLocalIdWithInfo, mkExportedLocalId,
+ mkLocalIdWithInfo, mkExportedLocalId, mkExportedVanillaId,
mkSysLocal, mkSysLocalM, mkSysLocalOrCoVar, mkSysLocalOrCoVarM,
mkUserLocal, mkUserLocalCoVar, mkUserLocalOrCoVar,
mkDerivedLocalCoVarM,
@@ -288,6 +288,10 @@ mkExportedLocalId :: IdDetails -> Name -> Type -> Id
mkExportedLocalId details name ty = Var.mkExportedLocalVar details name ty vanillaIdInfo
-- Note [Free type variables]
+mkExportedVanillaId :: Name -> Type -> Id
+mkExportedVanillaId name ty = Var.mkExportedLocalVar VanillaId name ty vanillaIdInfo
+ -- Note [Free type variables]
+
-- | Create a system local 'Id'. These are local 'Id's (see "Var#globalvslocal")
-- that are created by the compiler out of thin air
diff --git a/compiler/basicTypes/IdInfo.hs b/compiler/basicTypes/IdInfo.hs
index db32f053a2..64703f59f4 100644
--- a/compiler/basicTypes/IdInfo.hs
+++ b/compiler/basicTypes/IdInfo.hs
@@ -137,17 +137,6 @@ data IdDetails
| CoVarId -- ^ A coercion variable
- -- The rest are distinguished only for debugging reasons
- -- e.g. to suppress them in -ddump-types
- -- Currently we don't persist these through interface file
- -- (see MkIface.toIfaceIdDetails), but we easily could if it mattered
-
- | ReflectionId -- ^ A top-level Id to support runtime reflection
- -- e.g. $trModule, or $tcT
-
- | PatSynId -- ^ A top-level Id to support pattern synonyms;
- -- the builder or matcher for the pattern synonym
-
data RecSelParent = RecSelData TyCon | RecSelPatSyn PatSyn deriving Eq
-- Either `TyCon` or `PatSyn` depending
-- on the origin of the record selector.
@@ -177,8 +166,6 @@ pprIdDetails VanillaId = empty
pprIdDetails other = brackets (pp other)
where
pp VanillaId = panic "pprIdDetails"
- pp ReflectionId = ptext (sLit "ReflectionId")
- pp PatSynId = ptext (sLit "PatSynId")
pp (DataConWorkId _) = ptext (sLit "DataCon")
pp (DataConWrapId _) = ptext (sLit "DataConWrapper")
pp (ClassOpId {}) = ptext (sLit "ClassOp")
diff --git a/compiler/basicTypes/OccName.hs b/compiler/basicTypes/OccName.hs
index ad19f1f5fd..40614add32 100644
--- a/compiler/basicTypes/OccName.hs
+++ b/compiler/basicTypes/OccName.hs
@@ -56,7 +56,7 @@ module OccName (
mkDataConWrapperOcc, mkWorkerOcc,
mkMatcherOcc, mkBuilderOcc,
mkDefaultMethodOcc,
- mkDerivedTyConOcc, mkNewTyCoOcc, mkClassOpAuxOcc,
+ mkNewTyCoOcc, mkClassOpAuxOcc,
mkCon2TagOcc, mkTag2ConOcc, mkMaxTagOcc,
mkClassDataConOcc, mkDictOcc, mkIPOcc,
mkSpecOcc, mkForeignExportOcc, mkRepEqOcc,
@@ -551,10 +551,9 @@ a user-written type or function name
$pnC n'th superclass selector for class C
$wf Worker for function 'f'
$sf.. Specialised version of f
- T:C Tycon for dictionary for class C
D:C Data constructor for dictionary for class C
NTCo:T Coercion connecting newtype T with its representation type
- TFCo:R Coercion connecting a data family to its respresentation type R
+ TFCo:R Coercion connecting a data family to its representation type R
In encoded form these appear as Zdfxxx etc
@@ -575,16 +574,18 @@ mk_deriv :: NameSpace
mk_deriv occ_sp sys_prefix str = mkOccName occ_sp (sys_prefix ++ str)
isDerivedOccName :: OccName -> Bool
+-- ^ Test for definitions internally generated by GHC. This predicte
+-- is used to suppress printing of internal definitions in some debug prints
isDerivedOccName occ =
case occNameString occ of
- '$':c:_ | isAlphaNum c -> True
- ':':c:_ | isAlphaNum c -> True
+ '$':c:_ | isAlphaNum c -> True -- E.g. $wfoo
+ c:':':_ | isAlphaNum c -> True -- E.g. N:blah newtype coercions
_other -> False
mkDataConWrapperOcc, mkWorkerOcc,
mkMatcherOcc, mkBuilderOcc,
mkDefaultMethodOcc,
- mkDerivedTyConOcc, mkClassDataConOcc, mkDictOcc,
+ mkClassDataConOcc, mkDictOcc,
mkIPOcc, mkSpecOcc, mkForeignExportOcc, mkRepEqOcc,
mkGenR, mkGen1R, mkGenRCo,
mkDataTOcc, mkDataCOcc, mkDataConWorkerOcc, mkNewTyCoOcc,
@@ -600,16 +601,14 @@ mkMatcherOcc = mk_simple_deriv varName "$m"
mkBuilderOcc = mk_simple_deriv varName "$b"
mkDefaultMethodOcc = mk_simple_deriv varName "$dm"
mkClassOpAuxOcc = mk_simple_deriv varName "$c"
-mkDerivedTyConOcc = mk_simple_deriv tcName ":" -- The : prefix makes sure it classifies as a tycon/datacon
-mkClassDataConOcc = mk_simple_deriv dataName "D:" -- We go straight to the "real" data con
- -- for datacons from classes
mkDictOcc = mk_simple_deriv varName "$d"
mkIPOcc = mk_simple_deriv varName "$i"
mkSpecOcc = mk_simple_deriv varName "$s"
mkForeignExportOcc = mk_simple_deriv varName "$f"
-mkRepEqOcc = mk_simple_deriv tvName "$r" -- In RULES involving Coercible
-mkNewTyCoOcc = mk_simple_deriv tcName "NTCo:" -- Coercion for newtypes
-mkInstTyCoOcc = mk_simple_deriv tcName "TFCo:" -- Coercion for type functions
+mkRepEqOcc = mk_simple_deriv tvName "$r" -- In RULES involving Coercible
+mkClassDataConOcc = mk_simple_deriv dataName "C:" -- Data con for a class
+mkNewTyCoOcc = mk_simple_deriv tcName "N:" -- Coercion for newtypes
+mkInstTyCoOcc = mk_simple_deriv tcName "D:" -- Coercion for type functions
mkEqPredCoOcc = mk_simple_deriv tcName "$co"
-- Used in derived instances
diff --git a/compiler/deSugar/DsExpr.hs b/compiler/deSugar/DsExpr.hs
index cfa68338ea..5d3f7c7689 100644
--- a/compiler/deSugar/DsExpr.hs
+++ b/compiler/deSugar/DsExpr.hs
@@ -59,7 +59,6 @@ import FastString
import PatSyn
import IfaceEnv
-import IdInfo
import Data.IORef ( atomicModifyIORef', modifyIORef )
import Control.Monad
@@ -461,7 +460,7 @@ dsExpr (HsStatic expr@(L loc _)) = do
let tvars = tyCoVarsOfTypeWellScoped ty
speTy = ASSERT( all isTyVar tvars ) -- ty is top-level, so this is OK
mkInvForAllTys tvars $ mkTyConApp staticPtrTyCon [ty]
- speId = mkExportedLocalId VanillaId n' speTy
+ speId = mkExportedVanillaId n' speTy
fp@(Fingerprint w0 w1) = fingerprintName $ idName speId
fp_core = mkConApp fingerprintDataCon
[ mkWord64LitWordRep dflags w0
diff --git a/compiler/iface/MkIface.hs b/compiler/iface/MkIface.hs
index d44a1975e3..9e4c30355c 100644
--- a/compiler/iface/MkIface.hs
+++ b/compiler/iface/MkIface.hs
@@ -1649,11 +1649,6 @@ toIfaceIdDetails (RecSelId { sel_naughty = n
RecSelPatSyn pat_syn -> Right (patSynToIfaceDecl pat_syn)
in IfRecSelId iface n
- -- Currently we don't persist these three "advisory" IdInfos
- -- through interface files. We easily could if it mattered
-toIfaceIdDetails PatSynId = IfVanillaId
-toIfaceIdDetails ReflectionId = IfVanillaId
-
-- The remaining cases are all "implicit Ids" which don't
-- appear in interface files at all
toIfaceIdDetails other = pprTrace "toIfaceIdDetails" (ppr other)
diff --git a/compiler/typecheck/TcEnv.hs b/compiler/typecheck/TcEnv.hs
index aa87b0ecf8..17a9b9bf97 100644
--- a/compiler/typecheck/TcEnv.hs
+++ b/compiler/typecheck/TcEnv.hs
@@ -74,7 +74,6 @@ import LoadIface
import PrelNames
import TysWiredIn
import Id
-import IdInfo( IdDetails(VanillaId) )
import Var
import VarSet
import RdrName
@@ -871,9 +870,9 @@ newGlobalBinder.
newFamInstTyConName :: Located Name -> [Type] -> TcM Name
newFamInstTyConName (L loc name) tys = mk_fam_inst_name id loc name [tys]
-newFamInstAxiomName :: SrcSpan -> Name -> [CoAxBranch] -> TcM Name
-newFamInstAxiomName loc name branches
- = mk_fam_inst_name mkInstTyCoOcc loc name (map coAxBranchLHS branches)
+newFamInstAxiomName :: Located Name -> [[Type]] -> TcM Name
+newFamInstAxiomName (L loc name) branches
+ = mk_fam_inst_name mkInstTyCoOcc loc name branches
mk_fam_inst_name :: (OccName -> OccName) -> SrcSpan -> Name -> [[Type]] -> TcM Name
mk_fam_inst_name adaptOcc loc tc_name tyss
@@ -901,7 +900,7 @@ mkStableIdFromString str sig_ty loc occ_wrapper = do
name <- mkWrapperName "stable" str
let occ = mkVarOccFS name :: OccName
gnm = mkExternalName uniq mod (occ_wrapper occ) loc :: Name
- id = mkExportedLocalId VanillaId gnm sig_ty :: Id
+ id = mkExportedVanillaId gnm sig_ty :: Id
return id
mkStableIdFromName :: Name -> Type -> SrcSpan -> (OccName -> OccName) -> TcM TcId
diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs
index 47cd73b589..4f0456852d 100644
--- a/compiler/typecheck/TcInstDcls.hs
+++ b/compiler/typecheck/TcInstDcls.hs
@@ -623,8 +623,7 @@ tcTyFamInstDecl mb_clsinfo (L loc decl@(TyFamInstDecl { tfid_eqn = eqn }))
; checkValidCoAxBranch mb_clsinfo fam_tc co_ax_branch
-- (3) construct coercion axiom
- ; rep_tc_name <- newFamInstAxiomName loc (unLoc fam_lname)
- [co_ax_branch]
+ ; rep_tc_name <- newFamInstAxiomName fam_lname [coAxBranchLHS co_ax_branch]
; let axiom = mkUnbranchedCoAxiom rep_tc_name fam_tc co_ax_branch
; newFamInst SynFamilyInst axiom }
@@ -667,7 +666,7 @@ tcDataFamInstDecl mb_clsinfo
-- Construct representation tycon
; rep_tc_name <- newFamInstTyConName fam_tc_name pats'
- ; axiom_name <- newImplicitBinder rep_tc_name mkInstTyCoOcc
+ ; axiom_name <- newFamInstAxiomName fam_tc_name [pats']
; let (eta_pats, etad_tvs) = eta_reduce pats'
eta_tvs = filterOut (`elem` etad_tvs) tvs'
full_tvs = eta_tvs ++ etad_tvs
diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs
index 078b7dfac3..da2aa7416d 100644
--- a/compiler/typecheck/TcRnDriver.hs
+++ b/compiler/typecheck/TcRnDriver.hs
@@ -828,7 +828,7 @@ checkHiBootIface'
; return Nothing }
(dfun:_) -> return (Just (local_boot_dfun, dfun))
where
- local_boot_dfun = Id.mkExportedLocalId VanillaId boot_dfun_name (idType dfun)
+ local_boot_dfun = Id.mkExportedVanillaId boot_dfun_name (idType dfun)
-- Name from the /boot-file/ ClsInst, but type from the dfun
-- defined in /this module/. That ensures that the TyCon etc
-- inside the type are the ones defined in this module, not
@@ -1484,8 +1484,8 @@ check_main dflags tcg_env explicit_mod_hdr
; let { root_main_name = mkExternalName rootMainKey rOOT_MAIN
(mkVarOccFS (fsLit "main"))
(getSrcSpan main_name)
- ; root_main_id = Id.mkExportedLocalId VanillaId root_main_name
- (mkTyConApp ioTyCon [res_ty])
+ ; root_main_id = Id.mkExportedVanillaId root_main_name
+ (mkTyConApp ioTyCon [res_ty])
; co = mkWpTyApps [res_ty]
; rhs = nlHsApp (mkLHsWrap co (nlHsVar run_main_id)) main_expr
; main_bind = mkVarBind root_main_id rhs }
@@ -2414,10 +2414,9 @@ ppr_types type_env
= True
| otherwise
= isExternalName (idName id) &&
- (case idDetails id of { VanillaId -> True; _ -> False })
- -- Looking for VanillaId ignores data constructors, records selectors etc.
- -- The isExternalName ignores local evidence bindings that the type checker
- -- has invented. Top-level user-defined things have External names.
+ (not (isDerivedOccName (getOccName id)))
+ -- Top-level user-defined things have External names.
+ -- Suppress internally-generated things unless -dppr-debug
ppr_tycons :: [FamInst] -> TypeEnv -> SDoc
ppr_tycons fam_insts type_env
diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs
index f6a5c9fbee..b7b27c286d 100644
--- a/compiler/typecheck/TcTyClsDecls.hs
+++ b/compiler/typecheck/TcTyClsDecls.hs
@@ -712,9 +712,23 @@ tcTyClDecl1 _parent rec_info
; return (tvs1', tvs2') }
tcFamDecl1 :: Maybe Class -> FamilyDecl Name -> TcM TyCon
-tcFamDecl1 parent (FamilyDecl { fdInfo = OpenTypeFamily, fdLName = L _ tc_name
+tcFamDecl1 parent (FamilyDecl { fdInfo = fam_info, fdLName = tc_lname@(L _ tc_name)
, fdTyVars = tvs, fdResultSig = L _ sig
, fdInjectivityAnn = inj })
+ | DataFamily <- fam_info
+ = tcTyClTyVars tc_name tvs $ \ kvs' tvs' tycon_kind res_kind -> do
+ { traceTc "data family:" (ppr tc_name)
+ ; checkFamFlag tc_name
+ ; extra_tvs <- tcDataKindSig res_kind
+ ; tc_rep_name <- newTyConRepName tc_name
+ ; let final_tvs = (kvs' ++ tvs') `chkAppend` extra_tvs -- we may not need these
+ tycon = mkFamilyTyCon tc_name tycon_kind final_tvs
+ (resultVariableName sig)
+ (DataFamilyTyCon tc_rep_name)
+ parent NotInjective
+ ; return tycon }
+
+ | OpenTypeFamily <- fam_info
= tcTyClTyVars tc_name tvs $ \ kvs' tvs' full_kind _res_kind -> do
{ traceTc "open type family:" (ppr tc_name)
; checkFamFlag tc_name
@@ -725,13 +739,10 @@ tcFamDecl1 parent (FamilyDecl { fdInfo = OpenTypeFamily, fdLName = L _ tc_name
parent inj'
; return tycon }
-tcFamDecl1 parent
- (FamilyDecl { fdInfo = ClosedTypeFamily mb_eqns
- , fdLName = L _ tc_name, fdTyVars = tvs
- , fdResultSig = L _ sig, fdInjectivityAnn = inj })
--- Closed type families are a little tricky, because they contain the definition
--- of both the type family and the equations for a CoAxiom.
- = do { traceTc "Closed type family:" (ppr tc_name)
+ | ClosedTypeFamily mb_eqns <- fam_info
+ = -- Closed type families are a little tricky, because they contain the definition
+ -- of both the type family and the equations for a CoAxiom.
+ do { traceTc "Closed type family:" (ppr tc_name)
-- the variables in the header scope only over the injectivity
-- declaration but this is not involved here
; (tvs', inj', kind) <- tcTyClTyVars tc_name tvs
@@ -769,8 +780,7 @@ tcFamDecl1 parent
-- because there will only be one axiom, so we don't need to
-- differentiate names.
-- See [Zonking inside the knot] in TcHsType
- ; loc <- getSrcSpanM
- ; co_ax_name <- newFamInstAxiomName loc tc_name []
+ ; co_ax_name <- newFamInstAxiomName tc_lname []
; let mb_co_ax
| null eqns = Nothing -- mkBranchedCoAxiom fails on empty list
@@ -779,26 +789,13 @@ tcFamDecl1 parent
fam_tc = mkFamilyTyCon tc_name kind tvs' (resultVariableName sig)
(ClosedSynFamilyTyCon mb_co_ax) parent inj'
+ -- We check for instance validity later, when doing validity
+ -- checking for the tycon. Exception: checking equations
+ -- overlap done by dropDominatedAxioms
; return fam_tc } }
--- We check for instance validity later, when doing validity checking for
--- the tycon. Exception: checking equations overlap done by dropDominatedAxioms
+ | otherwise = panic "tcFamInst1" -- Silence pattern-exhaustiveness checker
-tcFamDecl1 parent
- (FamilyDecl { fdInfo = DataFamily, fdLName = L _ tc_name
- , fdTyVars = tvs, fdResultSig = L _ sig })
- = tcTyClTyVars tc_name tvs $ \ kvs' tvs' tycon_kind res_kind -> do
- { traceTc "data family:" (ppr tc_name)
- ; checkFamFlag tc_name
- ; extra_tvs <- tcDataKindSig res_kind
- ; tc_rep_name <- newTyConRepName tc_name
- ; let final_tvs = (kvs' ++ tvs') `chkAppend` extra_tvs -- we may not need these
- tycon = mkFamilyTyCon tc_name tycon_kind final_tvs
- (resultVariableName sig)
- (DataFamilyTyCon tc_rep_name)
- parent NotInjective
-
- ; return tycon }
-- | Maybe return a list of Bools that say whether a type family was declared
-- injective in the corresponding type arguments. Length of the list is equal to
diff --git a/compiler/typecheck/TcTyDecls.hs b/compiler/typecheck/TcTyDecls.hs
index 47f5b64d10..c2f017d0cf 100644
--- a/compiler/typecheck/TcTyDecls.hs
+++ b/compiler/typecheck/TcTyDecls.hs
@@ -877,7 +877,7 @@ mkDefaultMethodIds :: [TyCon] -> [Id]
-- the filled-in default methods of each instance declaration
-- See Note [Default method Ids and Template Haskell]
mkDefaultMethodIds tycons
- = [ mkExportedLocalId VanillaId dm_name (mk_dm_ty cls sel_id dm_spec)
+ = [ mkExportedVanillaId dm_name (mk_dm_ty cls sel_id dm_spec)
| tc <- tycons
, Just cls <- [tyConClass_maybe tc]
, (sel_id, Just (dm_name, dm_spec)) <- classOpItems cls ]
diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs
index 032ff79cbf..b750340720 100644
--- a/compiler/typecheck/TcTypeable.hs
+++ b/compiler/typecheck/TcTypeable.hs
@@ -14,7 +14,6 @@ import TcEnv
import TcRnMonad
import PrelNames( gHC_TYPES, trModuleDataConName, trTyConDataConName, trNameSDataConName )
import Id
-import IdInfo( IdDetails(..) )
import Type
import TyCon
import DataCon
@@ -113,8 +112,8 @@ mkModIdBindings
; tr_mod_dc <- tcLookupDataCon trModuleDataConName
; tr_name_dc <- tcLookupDataCon trNameSDataConName
; mod_nm <- newGlobalBinder mod (mkVarOcc "$trModule") loc
- ; let mod_id = mkExportedLocalId ReflectionId mod_nm
- (mkTyConApp (dataConTyCon tr_mod_dc) [])
+ ; let mod_ty = mkTyConApp (dataConTyCon tr_mod_dc) []
+ mod_id = mkExportedVanillaId mod_nm mod_ty
mod_bind = mkVarBind mod_id mod_rhs
mod_rhs = nlHsApps (dataConWrapId tr_mod_dc)
[ trNameLit tr_name_dc (unitIdFS (moduleUnitId mod))
@@ -178,7 +177,7 @@ mkTyConRepBinds (dflags, mod_expr, pkg_str, mod_str, tr_datacon, trn_datacon) ty
= case tyConRepName_maybe tycon of
Just rep_name -> unitBag (mkVarBind rep_id rep_rhs)
where
- rep_id = mkExportedLocalId ReflectionId rep_name (mkTyConApp tr_tycon [])
+ rep_id = mkExportedVanillaId rep_name (mkTyConApp tr_tycon [])
_ -> emptyBag
where
tr_tycon = dataConTyCon tr_datacon
diff --git a/testsuite/tests/deSugar/should_compile/T2431.stderr b/testsuite/tests/deSugar/should_compile/T2431.stderr
index 0184513754..935285a0d1 100644
--- a/testsuite/tests/deSugar/should_compile/T2431.stderr
+++ b/testsuite/tests/deSugar/should_compile/T2431.stderr
@@ -26,7 +26,7 @@ a1 = GHC.Types.TrNameS "T2431"#
-- RHS size: {terms: 3, types: 0, coercions: 0}
T2431.$trModule :: GHC.Types.Module
-[GblId[ReflectionId], Caf=NoCafRefs, Str=DmdType]
+[GblId, Caf=NoCafRefs, Str=DmdType]
T2431.$trModule = GHC.Types.Module a a1
-- RHS size: {terms: 2, types: 0, coercions: 0}
@@ -36,7 +36,7 @@ a2 = GHC.Types.TrNameS "'Refl"#
-- RHS size: {terms: 5, types: 0, coercions: 0}
T2431.$tc'Refl :: GHC.Types.TyCon
-[GblId[ReflectionId], Caf=NoCafRefs, Str=DmdType]
+[GblId, Caf=NoCafRefs, Str=DmdType]
T2431.$tc'Refl =
GHC.Types.TyCon
15026191172322750497## 3898273167927206410## T2431.$trModule a2
@@ -48,7 +48,7 @@ a3 = GHC.Types.TrNameS ":~:"#
-- RHS size: {terms: 5, types: 0, coercions: 0}
T2431.$tc:~: :: GHC.Types.TyCon
-[GblId[ReflectionId], Caf=NoCafRefs, Str=DmdType]
+[GblId, Caf=NoCafRefs, Str=DmdType]
T2431.$tc:~: =
GHC.Types.TyCon
9759653149176674453## 12942818337407067047## T2431.$trModule a3
diff --git a/testsuite/tests/ghci/scripts/T4175.stdout b/testsuite/tests/ghci/scripts/T4175.stdout
index dbf2f371dd..ef5b5c69c1 100644
--- a/testsuite/tests/ghci/scripts/T4175.stdout
+++ b/testsuite/tests/ghci/scripts/T4175.stdout
@@ -1,19 +1,19 @@
type family A a b
Kind: * -> * -> *
-- Defined at T4175.hs:7:1
-type instance A (B a) b = () -- Defined at T4175.hs:10:1
-type instance A (Maybe a) a = a -- Defined at T4175.hs:9:1
-type instance A Int Int = () -- Defined at T4175.hs:8:1
+type instance A (B a) b = () -- Defined at T4175.hs:10:15
+type instance A (Maybe a) a = a -- Defined at T4175.hs:9:15
+type instance A Int Int = () -- Defined at T4175.hs:8:15
data family B a -- Defined at T4175.hs:12:1
instance G B -- Defined at T4175.hs:34:10
data instance B () = MkB -- Defined at T4175.hs:13:15
-type instance A (B a) b = () -- Defined at T4175.hs:10:1
+type instance A (B a) b = () -- Defined at T4175.hs:10:15
class C a where
type family D a b
Kind: * -> * -> *
-- Defined at T4175.hs:16:5
-type instance D () () = Bool -- Defined at T4175.hs:22:5
-type instance D Int () = String -- Defined at T4175.hs:19:5
+type instance D () () = Bool -- Defined at T4175.hs:22:10
+type instance D Int () = String -- Defined at T4175.hs:19:10
type family E a
Kind: * -> *
where
@@ -29,8 +29,8 @@ instance Ord () -- Defined in ‘GHC.Classes’
instance Read () -- Defined in ‘GHC.Read’
instance Show () -- Defined in ‘GHC.Show’
instance Monoid () -- Defined in ‘GHC.Base’
-type instance D () () = Bool -- Defined at T4175.hs:22:5
-type instance D Int () = String -- Defined at T4175.hs:19:5
+type instance D () () = Bool -- Defined at T4175.hs:22:10
+type instance D Int () = String -- Defined at T4175.hs:19:10
data instance B () = MkB -- Defined at T4175.hs:13:15
data Maybe a = Nothing | Just a -- Defined in ‘GHC.Base’
instance Eq a => Eq (Maybe a) -- Defined in ‘GHC.Base’
@@ -43,7 +43,7 @@ instance Applicative Maybe -- Defined in ‘GHC.Base’
instance Foldable Maybe -- Defined in ‘Data.Foldable’
instance Traversable Maybe -- Defined in ‘Data.Traversable’
instance Monoid a => Monoid (Maybe a) -- Defined in ‘GHC.Base’
-type instance A (Maybe a) a = a -- Defined at T4175.hs:9:1
+type instance A (Maybe a) a = a -- Defined at T4175.hs:9:15
data Int = I# Int# -- Defined in ‘GHC.Types’
instance C Int -- Defined at T4175.hs:18:10
instance Bounded Int -- Defined in ‘GHC.Enum’
@@ -55,7 +55,7 @@ instance Ord Int -- Defined in ‘GHC.Classes’
instance Read Int -- Defined in ‘GHC.Read’
instance Real Int -- Defined in ‘GHC.Real’
instance Show Int -- Defined in ‘GHC.Show’
-type instance D Int () = String -- Defined at T4175.hs:19:5
-type instance A Int Int = () -- Defined at T4175.hs:8:1
+type instance D Int () = String -- Defined at T4175.hs:19:10
+type instance A Int Int = () -- Defined at T4175.hs:8:15
class Z a -- Defined at T4175.hs:28:1
instance F (Z a) -- Defined at T4175.hs:31:10
diff --git a/testsuite/tests/ghci/scripts/T7939.stdout b/testsuite/tests/ghci/scripts/T7939.stdout
index ec6c75cca2..1e6c5b7548 100644
--- a/testsuite/tests/ghci/scripts/T7939.stdout
+++ b/testsuite/tests/ghci/scripts/T7939.stdout
@@ -6,7 +6,7 @@ Bar :: k -> * -> *
type family F a
Kind: * -> *
-- Defined at T7939.hs:8:1
-type instance F Int = Bool -- Defined at T7939.hs:9:1
+type instance F Int = Bool -- Defined at T7939.hs:9:15
F :: * -> *
type family G a
Kind: * -> *
diff --git a/testsuite/tests/indexed-types/should_compile/T3017.stderr b/testsuite/tests/indexed-types/should_compile/T3017.stderr
index 1300626e17..68214e946e 100644
--- a/testsuite/tests/indexed-types/should_compile/T3017.stderr
+++ b/testsuite/tests/indexed-types/should_compile/T3017.stderr
@@ -1,5 +1,8 @@
TYPE SIGNATURES
+ Foo.L :: forall a. [a] -> ListColl a
+ empty :: forall c. Coll c => c
emptyL :: forall a. ListColl a
+ insert :: forall c. Coll c => Elem c -> c -> c
test2 ::
forall c t t1. (Elem c ~ (t, t1), Coll c, Num t1, Num t) => c -> c
TYPE CONSTRUCTORS
@@ -12,7 +15,7 @@ TYPE CONSTRUCTORS
data ListColl a = L [a]
Kind: * -> *
COERCION AXIOMS
- axiom Foo.TFCo:R:ElemListColl ::
+ axiom Foo.D:R:ElemListColl ::
Elem (ListColl a) = a -- Defined at T3017.hs:13:9
INSTANCES
instance Coll (ListColl a) -- Defined at T3017.hs:12:11
@@ -20,4 +23,4 @@ FAMILY INSTANCES
type Elem (ListColl a)
Dependent modules: []
Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0,
- integer-gmp-1.0.0.0]
+ integer-gmp-1.0.0.1]
diff --git a/testsuite/tests/numeric/should_compile/T7116.stdout b/testsuite/tests/numeric/should_compile/T7116.stdout
index 373e3c5ec8..7853fa128b 100644
--- a/testsuite/tests/numeric/should_compile/T7116.stdout
+++ b/testsuite/tests/numeric/should_compile/T7116.stdout
@@ -22,7 +22,7 @@ T7116.$trModule1 = GHC.Types.TrNameS "T7116"#
-- RHS size: {terms: 3, types: 0, coercions: 0}
T7116.$trModule :: GHC.Types.Module
-[GblId[ReflectionId],
+[GblId,
Caf=NoCafRefs,
Str=DmdType m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
diff --git a/testsuite/tests/partial-sigs/should_compile/ADT.stderr b/testsuite/tests/partial-sigs/should_compile/ADT.stderr
index 0fe16d1ed5..0da9e2284a 100644
--- a/testsuite/tests/partial-sigs/should_compile/ADT.stderr
+++ b/testsuite/tests/partial-sigs/should_compile/ADT.stderr
@@ -1,4 +1,5 @@
TYPE SIGNATURES
+ ADT.Foo :: forall x y z. x -> y -> z -> Foo x y z
bar :: Int -> Foo Bool () Int
TYPE CONSTRUCTORS
data Foo x y z = Foo x y z
@@ -6,4 +7,4 @@ TYPE CONSTRUCTORS
COERCION AXIOMS
Dependent modules: []
Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0,
- integer-gmp-1.0.0.0]
+ integer-gmp-1.0.0.1]
diff --git a/testsuite/tests/partial-sigs/should_compile/DataFamilyInstanceLHS.stderr b/testsuite/tests/partial-sigs/should_compile/DataFamilyInstanceLHS.stderr
index 9698ab2c10..6a2ac84f6c 100644
--- a/testsuite/tests/partial-sigs/should_compile/DataFamilyInstanceLHS.stderr
+++ b/testsuite/tests/partial-sigs/should_compile/DataFamilyInstanceLHS.stderr
@@ -1,15 +1,25 @@
TYPE SIGNATURES
+ DataFamilyInstanceLHS.A :: MyKind
+ DataFamilyInstanceLHS.B :: MyKind
+ DataFamilyInstanceLHS.SingA ::
+ forall (_ :: MyKind).
+ (_ ~ 'A) =>
+ DataFamilyInstanceLHS.R:SingMyKind_ _
+ DataFamilyInstanceLHS.SingB ::
+ forall (_ :: MyKind).
+ (_ ~ 'B) =>
+ DataFamilyInstanceLHS.R:SingMyKind_ _
foo :: Sing 'A
TYPE CONSTRUCTORS
data MyKind = A | B
Kind: *
data family Sing (a :: k)
COERCION AXIOMS
- axiom DataFamilyInstanceLHS.TFCo:R:SingMyKind_ ::
+ axiom DataFamilyInstanceLHS.D:R:SingMyKind_0 ::
Sing = DataFamilyInstanceLHS.R:SingMyKind_
-- Defined at DataFamilyInstanceLHS.hs:8:15
FAMILY INSTANCES
data instance Sing
Dependent modules: []
Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0,
- integer-gmp-1.0.0.0]
+ integer-gmp-1.0.0.1]
diff --git a/testsuite/tests/partial-sigs/should_compile/NamedWildcardInDataFamilyInstanceLHS.stderr b/testsuite/tests/partial-sigs/should_compile/NamedWildcardInDataFamilyInstanceLHS.stderr
index 730c0ed571..b335118ed8 100644
--- a/testsuite/tests/partial-sigs/should_compile/NamedWildcardInDataFamilyInstanceLHS.stderr
+++ b/testsuite/tests/partial-sigs/should_compile/NamedWildcardInDataFamilyInstanceLHS.stderr
@@ -1,14 +1,24 @@
TYPE SIGNATURES
+ NamedWildcardInDataFamilyInstanceLHS.A :: MyKind
+ NamedWildcardInDataFamilyInstanceLHS.B :: MyKind
+ NamedWildcardInDataFamilyInstanceLHS.SingA ::
+ forall (_a :: MyKind).
+ (_a ~ 'A) =>
+ NamedWildcardInDataFamilyInstanceLHS.R:SingMyKind_a _a
+ NamedWildcardInDataFamilyInstanceLHS.SingB ::
+ forall (_a :: MyKind).
+ (_a ~ 'B) =>
+ NamedWildcardInDataFamilyInstanceLHS.R:SingMyKind_a _a
TYPE CONSTRUCTORS
data MyKind = A | B
Kind: *
data family Sing (a :: k)
COERCION AXIOMS
- axiom NamedWildcardInDataFamilyInstanceLHS.TFCo:R:SingMyKind_a ::
+ axiom NamedWildcardInDataFamilyInstanceLHS.D:R:SingMyKind_a0 ::
Sing = NamedWildcardInDataFamilyInstanceLHS.R:SingMyKind_a
-- Defined at NamedWildcardInDataFamilyInstanceLHS.hs:8:15
FAMILY INSTANCES
data instance Sing
Dependent modules: []
Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0,
- integer-gmp-1.0.0.0]
+ integer-gmp-1.0.0.1]
diff --git a/testsuite/tests/partial-sigs/should_compile/NamedWildcardInTypeFamilyInstanceLHS.stderr b/testsuite/tests/partial-sigs/should_compile/NamedWildcardInTypeFamilyInstanceLHS.stderr
index 84a7b4a55a..c39ff6f254 100644
--- a/testsuite/tests/partial-sigs/should_compile/NamedWildcardInTypeFamilyInstanceLHS.stderr
+++ b/testsuite/tests/partial-sigs/should_compile/NamedWildcardInTypeFamilyInstanceLHS.stderr
@@ -4,11 +4,11 @@ TYPE CONSTRUCTORS
Kind: * -> *
where
[_t] F _t = Int
- axiom NamedWildcardInTypeFamilyInstanceLHS.TFCo:R:F
+ axiom NamedWildcardInTypeFamilyInstanceLHS.D:R:F
COERCION AXIOMS
- axiom NamedWildcardInTypeFamilyInstanceLHS.TFCo:R:F ::
+ axiom NamedWildcardInTypeFamilyInstanceLHS.D:R:F ::
F _t = Int
-- Defined at NamedWildcardInTypeFamilyInstanceLHS.hs:5:3
Dependent modules: []
Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0,
- integer-gmp-1.0.0.0]
+ integer-gmp-1.0.0.1]
diff --git a/testsuite/tests/partial-sigs/should_compile/SkipMany.stderr b/testsuite/tests/partial-sigs/should_compile/SkipMany.stderr
index e67eeb095e..be635e620d 100644
--- a/testsuite/tests/partial-sigs/should_compile/SkipMany.stderr
+++ b/testsuite/tests/partial-sigs/should_compile/SkipMany.stderr
@@ -1,4 +1,6 @@
TYPE SIGNATURES
+ SkipMany.GenParser ::
+ forall tok st a. tok -> st -> a -> GenParser tok st a
skipMany ::
forall tok st a. GenParser tok st a -> GenParser tok st ()
skipMany' ::
@@ -9,4 +11,4 @@ TYPE CONSTRUCTORS
COERCION AXIOMS
Dependent modules: []
Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0,
- integer-gmp-1.0.0.0]
+ integer-gmp-1.0.0.1]
diff --git a/testsuite/tests/partial-sigs/should_compile/TypeFamilyInstanceLHS.stderr b/testsuite/tests/partial-sigs/should_compile/TypeFamilyInstanceLHS.stderr
index 2d5f52e357..0800286480 100644
--- a/testsuite/tests/partial-sigs/should_compile/TypeFamilyInstanceLHS.stderr
+++ b/testsuite/tests/partial-sigs/should_compile/TypeFamilyInstanceLHS.stderr
@@ -4,13 +4,13 @@ TYPE CONSTRUCTORS
type family F a b open
Kind: * -> * -> *
COERCION AXIOMS
- axiom TypeFamilyInstanceLHS.TFCo:R:FBool_ ::
+ axiom TypeFamilyInstanceLHS.D:R:FBool_ ::
F Bool _ = Bool -- Defined at TypeFamilyInstanceLHS.hs:6:15
- axiom TypeFamilyInstanceLHS.TFCo:R:FInt_ ::
+ axiom TypeFamilyInstanceLHS.D:R:FInt_ ::
F Int _ = Int -- Defined at TypeFamilyInstanceLHS.hs:5:15
FAMILY INSTANCES
type instance F Int _
type instance F Bool _
Dependent modules: []
Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0,
- integer-gmp-1.0.0.0]
+ integer-gmp-1.0.0.1]
diff --git a/testsuite/tests/roles/should_compile/Roles1.stderr b/testsuite/tests/roles/should_compile/Roles1.stderr
index ef67f90d8b..6ea24f009b 100644
--- a/testsuite/tests/roles/should_compile/Roles1.stderr
+++ b/testsuite/tests/roles/should_compile/Roles1.stderr
@@ -1,4 +1,11 @@
TYPE SIGNATURES
+ Roles1.K1 :: forall a. a -> T1 a
+ Roles1.K2 :: forall a. a -> T2 a
+ Roles1.K3 :: forall k (a :: k). T3 a
+ Roles1.K4 :: forall (a :: * -> *) b. a b -> T4 a b
+ Roles1.K5 :: forall a. a -> T5 a
+ Roles1.K6 :: forall k (a :: k). T6 a
+ Roles1.K7 :: forall k (a :: k) b. b -> T7 a b
TYPE CONSTRUCTORS
type role T1 nominal
data T1 a = K1 a
@@ -22,7 +29,7 @@ TYPE CONSTRUCTORS
COERCION AXIOMS
Dependent modules: []
Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0,
- integer-gmp-1.0.0.0]
+ integer-gmp-1.0.0.1]
==================== Typechecker ====================
Roles1.$tcT7
diff --git a/testsuite/tests/roles/should_compile/Roles13.stderr b/testsuite/tests/roles/should_compile/Roles13.stderr
index 8b7a2c8ce8..31795bf90b 100644
--- a/testsuite/tests/roles/should_compile/Roles13.stderr
+++ b/testsuite/tests/roles/should_compile/Roles13.stderr
@@ -14,7 +14,7 @@ a1 = GHC.Types.TrNameS "Roles13"#
-- RHS size: {terms: 3, types: 0, coercions: 0}
Roles13.$trModule :: GHC.Types.Module
-[GblId[ReflectionId], Caf=NoCafRefs, Str=DmdType]
+[GblId, Caf=NoCafRefs, Str=DmdType]
Roles13.$trModule = GHC.Types.Module a a1
-- RHS size: {terms: 2, types: 0, coercions: 0}
@@ -24,8 +24,10 @@ a2 = GHC.Types.TrNameS "'MkAge"#
-- RHS size: {terms: 5, types: 0, coercions: 0}
Roles13.$tc'MkAge :: GHC.Types.TyCon
-[GblId[ReflectionId], Caf=NoCafRefs, Str=DmdType]
-Roles13.$tc'MkAge = GHC.Types.TyCon 0## 0## Roles13.$trModule a2
+[GblId, Caf=NoCafRefs, Str=DmdType]
+Roles13.$tc'MkAge =
+ GHC.Types.TyCon
+ 1226019810264079099## 12180888342844277416## Roles13.$trModule a2
-- RHS size: {terms: 2, types: 0, coercions: 0}
a3 :: GHC.Types.TrName
@@ -34,8 +36,10 @@ a3 = GHC.Types.TrNameS "Age"#
-- RHS size: {terms: 5, types: 0, coercions: 0}
Roles13.$tcAge :: GHC.Types.TyCon
-[GblId[ReflectionId], Caf=NoCafRefs, Str=DmdType]
-Roles13.$tcAge = GHC.Types.TyCon 0## 0## Roles13.$trModule a3
+[GblId, Caf=NoCafRefs, Str=DmdType]
+Roles13.$tcAge =
+ GHC.Types.TyCon
+ 18304088376370610314## 1954648846714895105## Roles13.$trModule a3
-- RHS size: {terms: 2, types: 0, coercions: 0}
a4 :: GHC.Types.TrName
@@ -44,8 +48,10 @@ a4 = GHC.Types.TrNameS "'MkWrap"#
-- RHS size: {terms: 5, types: 0, coercions: 0}
Roles13.$tc'MkWrap :: GHC.Types.TyCon
-[GblId[ReflectionId], Caf=NoCafRefs, Str=DmdType]
-Roles13.$tc'MkWrap = GHC.Types.TyCon 0## 0## Roles13.$trModule a4
+[GblId, Caf=NoCafRefs, Str=DmdType]
+Roles13.$tc'MkWrap =
+ GHC.Types.TyCon
+ 12402878715225676312## 13345418993613492500## Roles13.$trModule a4
-- RHS size: {terms: 2, types: 0, coercions: 0}
a5 :: GHC.Types.TrName
@@ -54,8 +60,10 @@ a5 = GHC.Types.TrNameS "Wrap"#
-- RHS size: {terms: 5, types: 0, coercions: 0}
Roles13.$tcWrap :: GHC.Types.TyCon
-[GblId[ReflectionId], Caf=NoCafRefs, Str=DmdType]
-Roles13.$tcWrap = GHC.Types.TyCon 0## 0## Roles13.$trModule a5
+[GblId, Caf=NoCafRefs, Str=DmdType]
+Roles13.$tcWrap =
+ GHC.Types.TyCon
+ 5278920226786541118## 14554440859491798587## Roles13.$trModule a5
-- RHS size: {terms: 2, types: 2, coercions: 0}
a6 :: Wrap Age -> Wrap Age
@@ -67,7 +75,7 @@ convert :: Wrap Age -> Int
[GblId, Arity=1, Caf=NoCafRefs, Str=DmdType]
convert =
a6
- `cast` (<Wrap Age>_R -> Roles13.NTCo:Wrap[0] Roles13.NTCo:Age[0]
+ `cast` (<Wrap Age>_R -> Roles13.N:Wrap[0] Roles13.N:Age[0]
:: (Wrap Age -> Wrap Age) ~R# (Wrap Age -> Int))
diff --git a/testsuite/tests/roles/should_compile/Roles14.stderr b/testsuite/tests/roles/should_compile/Roles14.stderr
index aeff4498ba..b34194db79 100644
--- a/testsuite/tests/roles/should_compile/Roles14.stderr
+++ b/testsuite/tests/roles/should_compile/Roles14.stderr
@@ -1,22 +1,29 @@
TYPE SIGNATURES
+ meth2 :: forall a. C2 a => a -> a
TYPE CONSTRUCTORS
type role C2 representational
class C2 a where
meth2 :: a -> a
{-# MINIMAL meth2 #-}
COERCION AXIOMS
- axiom Roles12.NTCo:C2 :: C2 a = a -> a -- Defined at Roles14.hs:6:1
+ axiom Roles12.N:C2 :: C2 a = a -> a -- Defined at Roles14.hs:6:1
Dependent modules: []
Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0,
- integer-gmp-1.0.0.0]
+ integer-gmp-1.0.0.1]
==================== Typechecker ====================
Roles12.$tcC2
= GHC.Types.TyCon
- 0## 0## Roles12.$trModule (GHC.Types.TrNameS "C2"#)
-Roles12.$tc'D:C2
+ 4006088231579841122##
+ 4783761708993822739##
+ Roles12.$trModule
+ (GHC.Types.TrNameS "C2"#)
+Roles12.$tc'C:C2
= GHC.Types.TyCon
- 0## 0## Roles12.$trModule (GHC.Types.TrNameS "'D:C2"#)
+ 5555822832309788726##
+ 2795860317217328413##
+ Roles12.$trModule
+ (GHC.Types.TrNameS "'C:C2"#)
Roles12.$trModule
= GHC.Types.Module
(GHC.Types.TrNameS "main"#) (GHC.Types.TrNameS "Roles12"#)
diff --git a/testsuite/tests/roles/should_compile/Roles2.stderr b/testsuite/tests/roles/should_compile/Roles2.stderr
index 14d24b0150..7c075b9bce 100644
--- a/testsuite/tests/roles/should_compile/Roles2.stderr
+++ b/testsuite/tests/roles/should_compile/Roles2.stderr
@@ -1,4 +1,6 @@
TYPE SIGNATURES
+ Roles2.K1 :: forall a. IO a -> T1 a
+ Roles2.K2 :: forall a. FunPtr a -> T2 a
TYPE CONSTRUCTORS
data T1 a = K1 (IO a)
Kind: * -> *
@@ -8,21 +10,33 @@ TYPE CONSTRUCTORS
COERCION AXIOMS
Dependent modules: []
Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0,
- integer-gmp-1.0.0.0]
+ integer-gmp-1.0.0.1]
==================== Typechecker ====================
Roles2.$tcT2
= GHC.Types.TyCon
- 0## 0## Roles2.$trModule (GHC.Types.TrNameS "T2"#)
+ 5934726586329293381##
+ 1923031187495159753##
+ Roles2.$trModule
+ (GHC.Types.TrNameS "T2"#)
Roles2.$tc'K2
= GHC.Types.TyCon
- 0## 0## Roles2.$trModule (GHC.Types.TrNameS "'K2"#)
+ 1362115092449420584##
+ 15899377929296700609##
+ Roles2.$trModule
+ (GHC.Types.TrNameS "'K2"#)
Roles2.$tcT1
= GHC.Types.TyCon
- 0## 0## Roles2.$trModule (GHC.Types.TrNameS "T1"#)
+ 13879106829711353992##
+ 15151456821588362072##
+ Roles2.$trModule
+ (GHC.Types.TrNameS "T1"#)
Roles2.$tc'K1
= GHC.Types.TyCon
- 0## 0## Roles2.$trModule (GHC.Types.TrNameS "'K1"#)
+ 14735176013935828521##
+ 17563925141462511949##
+ Roles2.$trModule
+ (GHC.Types.TrNameS "'K1"#)
Roles2.$trModule
= GHC.Types.Module
(GHC.Types.TrNameS "main"#) (GHC.Types.TrNameS "Roles2"#)
diff --git a/testsuite/tests/roles/should_compile/Roles3.stderr b/testsuite/tests/roles/should_compile/Roles3.stderr
index bf6dd003e9..544e497c2d 100644
--- a/testsuite/tests/roles/should_compile/Roles3.stderr
+++ b/testsuite/tests/roles/should_compile/Roles3.stderr
@@ -1,4 +1,8 @@
TYPE SIGNATURES
+ meth1 :: forall a. C1 a => a -> a
+ meth2 :: forall a b. (C2 a b, a ~ b) => a -> b
+ meth3 :: forall a b. C3 a b => a -> F3 b -> F3 b
+ meth4 :: forall a b. C4 a b => a -> F4 b -> F4 b
TYPE CONSTRUCTORS
class C1 a where
meth1 :: a -> a
@@ -19,42 +23,66 @@ TYPE CONSTRUCTORS
type Syn1 a = F4 a
type Syn2 a = [a]
COERCION AXIOMS
- axiom Roles3.NTCo:C1 :: C1 a = a -> a -- Defined at Roles3.hs:6:1
- axiom Roles3.NTCo:C2 ::
+ axiom Roles3.N:C1 :: C1 a = a -> a -- Defined at Roles3.hs:6:1
+ axiom Roles3.N:C2 ::
C2 a b = (a ~ b) => a -> b -- Defined at Roles3.hs:9:1
- axiom Roles3.NTCo:C3 ::
+ axiom Roles3.N:C3 ::
C3 a b = a -> F3 b -> F3 b -- Defined at Roles3.hs:12:1
- axiom Roles3.NTCo:C4 ::
+ axiom Roles3.N:C4 ::
C4 a b = a -> F4 b -> F4 b -- Defined at Roles3.hs:18:1
Dependent modules: []
Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0,
- integer-gmp-1.0.0.0]
+ integer-gmp-1.0.0.1]
==================== Typechecker ====================
Roles3.$tcC4
= GHC.Types.TyCon
- 0## 0## Roles3.$trModule (GHC.Types.TrNameS "C4"#)
-Roles3.$tc'D:C4
+ 12861862461396457184##
+ 6389612623460961504##
+ Roles3.$trModule
+ (GHC.Types.TrNameS "C4"#)
+Roles3.$tc'C:C4
= GHC.Types.TyCon
- 0## 0## Roles3.$trModule (GHC.Types.TrNameS "'D:C4"#)
+ 5012080351591218464##
+ 14312195554521420369##
+ Roles3.$trModule
+ (GHC.Types.TrNameS "'C:C4"#)
Roles3.$tcC3
= GHC.Types.TyCon
- 0## 0## Roles3.$trModule (GHC.Types.TrNameS "C3"#)
-Roles3.$tc'D:C3
+ 5998139369941479154##
+ 6816352641934636458##
+ Roles3.$trModule
+ (GHC.Types.TrNameS "C3"#)
+Roles3.$tc'C:C3
= GHC.Types.TyCon
- 0## 0## Roles3.$trModule (GHC.Types.TrNameS "'D:C3"#)
+ 5363370173992879615##
+ 3444510123613553605##
+ Roles3.$trModule
+ (GHC.Types.TrNameS "'C:C3"#)
Roles3.$tcC2
= GHC.Types.TyCon
- 0## 0## Roles3.$trModule (GHC.Types.TrNameS "C2"#)
-Roles3.$tc'D:C2
+ 8833962732139387711##
+ 7891126688522429937##
+ Roles3.$trModule
+ (GHC.Types.TrNameS "C2"#)
+Roles3.$tc'C:C2
= GHC.Types.TyCon
- 0## 0## Roles3.$trModule (GHC.Types.TrNameS "'D:C2"#)
+ 17372867324718144313##
+ 13604113872247370917##
+ Roles3.$trModule
+ (GHC.Types.TrNameS "'C:C2"#)
Roles3.$tcC1
= GHC.Types.TyCon
- 0## 0## Roles3.$trModule (GHC.Types.TrNameS "C1"#)
-Roles3.$tc'D:C1
+ 16242970448469140073##
+ 10229725431456576413##
+ Roles3.$trModule
+ (GHC.Types.TrNameS "C1"#)
+Roles3.$tc'C:C1
= GHC.Types.TyCon
- 0## 0## Roles3.$trModule (GHC.Types.TrNameS "'D:C1"#)
+ 2927144765823607117##
+ 15172069236577673237##
+ Roles3.$trModule
+ (GHC.Types.TrNameS "'C:C1"#)
Roles3.$trModule
= GHC.Types.Module
(GHC.Types.TrNameS "main"#) (GHC.Types.TrNameS "Roles3"#)
diff --git a/testsuite/tests/roles/should_compile/Roles4.stderr b/testsuite/tests/roles/should_compile/Roles4.stderr
index 7253f93507..6a336da26b 100644
--- a/testsuite/tests/roles/should_compile/Roles4.stderr
+++ b/testsuite/tests/roles/should_compile/Roles4.stderr
@@ -1,4 +1,6 @@
TYPE SIGNATURES
+ meth1 :: forall a. C1 a => a -> a
+ meth3 :: forall a. C3 a => a -> Syn1 a
TYPE CONSTRUCTORS
class C1 a where
meth1 :: a -> a
@@ -8,26 +10,38 @@ TYPE CONSTRUCTORS
{-# MINIMAL meth3 #-}
type Syn1 a = [a]
COERCION AXIOMS
- axiom Roles4.NTCo:C1 :: C1 a = a -> a -- Defined at Roles4.hs:6:1
- axiom Roles4.NTCo:C3 ::
+ axiom Roles4.N:C1 :: C1 a = a -> a -- Defined at Roles4.hs:6:1
+ axiom Roles4.N:C3 ::
C3 a = a -> Syn1 a -- Defined at Roles4.hs:11:1
Dependent modules: []
Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0,
- integer-gmp-1.0.0.0]
+ integer-gmp-1.0.0.1]
==================== Typechecker ====================
Roles4.$tcC3
= GHC.Types.TyCon
- 0## 0## Roles4.$trModule (GHC.Types.TrNameS "C3"#)
-Roles4.$tc'D:C3
+ 16502190608089501863##
+ 13971441568961069854##
+ Roles4.$trModule
+ (GHC.Types.TrNameS "C3"#)
+Roles4.$tc'C:C3
= GHC.Types.TyCon
- 0## 0## Roles4.$trModule (GHC.Types.TrNameS "'D:C3"#)
+ 16482122951248115051##
+ 8497036782794772516##
+ Roles4.$trModule
+ (GHC.Types.TrNameS "'C:C3"#)
Roles4.$tcC1
= GHC.Types.TyCon
- 0## 0## Roles4.$trModule (GHC.Types.TrNameS "C1"#)
-Roles4.$tc'D:C1
+ 11951908835899020229##
+ 6518430686554778113##
+ Roles4.$trModule
+ (GHC.Types.TrNameS "C1"#)
+Roles4.$tc'C:C1
= GHC.Types.TyCon
- 0## 0## Roles4.$trModule (GHC.Types.TrNameS "'D:C1"#)
+ 11393997571952951642##
+ 4382794907973051606##
+ Roles4.$trModule
+ (GHC.Types.TrNameS "'C:C1"#)
Roles4.$trModule
= GHC.Types.Module
(GHC.Types.TrNameS "main"#) (GHC.Types.TrNameS "Roles4"#)
diff --git a/testsuite/tests/roles/should_compile/T8958.stderr b/testsuite/tests/roles/should_compile/T8958.stderr
index ba97e8a45f..4434b1ee74 100644
--- a/testsuite/tests/roles/should_compile/T8958.stderr
+++ b/testsuite/tests/roles/should_compile/T8958.stderr
@@ -2,6 +2,7 @@
T8958.hs:1:31: warning:
-XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
TYPE SIGNATURES
+ T8958.MkMap :: forall k v. [(k, v)] -> Map k v
TYPE CONSTRUCTORS
type role Map nominal representational
newtype (Nominal k, Representational v) => Map k v = MkMap [(k, v)]
@@ -10,35 +11,52 @@ TYPE CONSTRUCTORS
type role Representational representational
class Representational a
COERCION AXIOMS
- axiom T8958.NTCo:Map ::
- Map k v = [(k, v)] -- Defined at T8958.hs:13:1
+ axiom T8958.N:Map :: Map k v = [(k, v)] -- Defined at T8958.hs:13:1
INSTANCES
instance [incoherent] Nominal a -- Defined at T8958.hs:7:10
instance [incoherent] Representational a
-- Defined at T8958.hs:10:10
Dependent modules: []
Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0,
- integer-gmp-1.0.0.0]
+ integer-gmp-1.0.0.1]
==================== Typechecker ====================
T8958.$tcMap
= GHC.Types.TyCon
- 0## 0## T8958.$trModule (GHC.Types.TrNameS "Map"#)
+ 11173210732975605893##
+ 6338753504925142034##
+ T8958.$trModule
+ (GHC.Types.TrNameS "Map"#)
T8958.$tc'MkMap
= GHC.Types.TyCon
- 0## 0## T8958.$trModule (GHC.Types.TrNameS "'MkMap"#)
+ 10702411725744601909##
+ 8660532495248702786##
+ T8958.$trModule
+ (GHC.Types.TrNameS "'MkMap"#)
T8958.$tcRepresentational
= GHC.Types.TyCon
- 0## 0## T8958.$trModule (GHC.Types.TrNameS "Representational"#)
-T8958.$tc'D:Representational
+ 17939208465687456137##
+ 86959701938445380##
+ T8958.$trModule
+ (GHC.Types.TrNameS "Representational"#)
+T8958.$tc'C:Representational
= GHC.Types.TyCon
- 0## 0## T8958.$trModule (GHC.Types.TrNameS "'D:Representational"#)
+ 6623579006299218188##
+ 18041743345929230411##
+ T8958.$trModule
+ (GHC.Types.TrNameS "'C:Representational"#)
T8958.$tcNominal
= GHC.Types.TyCon
- 0## 0## T8958.$trModule (GHC.Types.TrNameS "Nominal"#)
-T8958.$tc'D:Nominal
+ 5048799062136959048##
+ 4899664595355811926##
+ T8958.$trModule
+ (GHC.Types.TrNameS "Nominal"#)
+T8958.$tc'C:Nominal
= GHC.Types.TyCon
- 0## 0## T8958.$trModule (GHC.Types.TrNameS "'D:Nominal"#)
+ 13167926310643805202##
+ 1726092271306256063##
+ T8958.$trModule
+ (GHC.Types.TrNameS "'C:Nominal"#)
T8958.$trModule
= GHC.Types.Module
(GHC.Types.TrNameS "main"#) (GHC.Types.TrNameS "T8958"#)
@@ -49,7 +67,7 @@ AbsBinds [a] []
Exported types: T8958.$fRepresentationala
:: forall a. Representational a
[LclIdX[DFunId], Str=DmdType]
- Binds: $dRepresentational = T8958.D:Representational
+ Binds: $dRepresentational = T8958.C:Representational
Evidence: [EvBinds{}]}
AbsBinds [a] []
{Exports: [T8958.$fNominala <= $dNominal
@@ -57,5 +75,6 @@ AbsBinds [a] []
<>]
Exported types: T8958.$fNominala :: forall a. Nominal a
[LclIdX[DFunId], Str=DmdType]
- Binds: $dNominal = T8958.D:Nominal
+ Binds: $dNominal = T8958.C:Nominal
Evidence: [EvBinds{}]}
+
diff --git a/testsuite/tests/simplCore/should_compile/T3717.stderr b/testsuite/tests/simplCore/should_compile/T3717.stderr
index cdfc5f5069..b66f49fa83 100644
--- a/testsuite/tests/simplCore/should_compile/T3717.stderr
+++ b/testsuite/tests/simplCore/should_compile/T3717.stderr
@@ -22,7 +22,7 @@ T3717.$trModule1 = GHC.Types.TrNameS "T3717"#
-- RHS size: {terms: 3, types: 0, coercions: 0}
T3717.$trModule :: GHC.Types.Module
-[GblId[ReflectionId],
+[GblId,
Caf=NoCafRefs,
Str=DmdType m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
diff --git a/testsuite/tests/simplCore/should_compile/T3772.stdout b/testsuite/tests/simplCore/should_compile/T3772.stdout
index 679d1eb2f6..aab671620c 100644
--- a/testsuite/tests/simplCore/should_compile/T3772.stdout
+++ b/testsuite/tests/simplCore/should_compile/T3772.stdout
@@ -47,7 +47,7 @@ T3772.$trModule2 = GHC.Types.TrNameS "main"#
-- RHS size: {terms: 3, types: 0, coercions: 0}
T3772.$trModule :: GHC.Types.Module
-[GblId[ReflectionId],
+[GblId,
Caf=NoCafRefs,
Str=DmdType m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
diff --git a/testsuite/tests/simplCore/should_compile/T4201.stdout b/testsuite/tests/simplCore/should_compile/T4201.stdout
index 51b159627e..384c62aa4c 100644
--- a/testsuite/tests/simplCore/should_compile/T4201.stdout
+++ b/testsuite/tests/simplCore/should_compile/T4201.stdout
@@ -1,3 +1,3 @@
{- Arity: 1, HasNoCafRefs, Strictness: <S,1*U()>m,
Unfolding: InlineRule (0, True, True)
- bof `cast` (Sym (NTCo:Foo[0]) ->_R <T>_R) -}
+ bof `cast` (Sym (N:Foo[0]) ->_R <T>_R) -}
diff --git a/testsuite/tests/simplCore/should_compile/T4908.stderr b/testsuite/tests/simplCore/should_compile/T4908.stderr
index bb0b08f53e..232e8c8ae8 100644
--- a/testsuite/tests/simplCore/should_compile/T4908.stderr
+++ b/testsuite/tests/simplCore/should_compile/T4908.stderr
@@ -22,7 +22,7 @@ T4908.$trModule1 = GHC.Types.TrNameS "T4908"#
-- RHS size: {terms: 3, types: 0, coercions: 0}
T4908.$trModule :: Module
-[GblId[ReflectionId],
+[GblId,
Caf=NoCafRefs,
Str=DmdType m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
diff --git a/testsuite/tests/simplCore/should_compile/T4930.stderr b/testsuite/tests/simplCore/should_compile/T4930.stderr
index d7d97d5ab0..5d1daffc0f 100644
--- a/testsuite/tests/simplCore/should_compile/T4930.stderr
+++ b/testsuite/tests/simplCore/should_compile/T4930.stderr
@@ -22,7 +22,7 @@ T4930.$trModule1 = GHC.Types.TrNameS "T4930"#
-- RHS size: {terms: 3, types: 0, coercions: 0}
T4930.$trModule :: GHC.Types.Module
-[GblId[ReflectionId],
+[GblId,
Caf=NoCafRefs,
Str=DmdType m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
diff --git a/testsuite/tests/simplCore/should_compile/T7360.stderr b/testsuite/tests/simplCore/should_compile/T7360.stderr
index ca398ec6dc..ac570df364 100644
--- a/testsuite/tests/simplCore/should_compile/T7360.stderr
+++ b/testsuite/tests/simplCore/should_compile/T7360.stderr
@@ -41,7 +41,7 @@ T7360.$trModule1 = GHC.Types.TrNameS "T7360"#
-- RHS size: {terms: 3, types: 0, coercions: 0}
T7360.$trModule :: GHC.Types.Module
-[GblId[ReflectionId],
+[GblId,
Caf=NoCafRefs,
Str=DmdType m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
@@ -60,7 +60,7 @@ T7360.$tc'Foo6 = GHC.Types.TrNameS "'Foo3"#
-- RHS size: {terms: 5, types: 0, coercions: 0}
T7360.$tc'Foo3 :: GHC.Types.TyCon
-[GblId[ReflectionId],
+[GblId,
Caf=NoCafRefs,
Str=DmdType m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
@@ -83,7 +83,7 @@ T7360.$tc'Foo5 = GHC.Types.TrNameS "'Foo2"#
-- RHS size: {terms: 5, types: 0, coercions: 0}
T7360.$tc'Foo2 :: GHC.Types.TyCon
-[GblId[ReflectionId],
+[GblId,
Caf=NoCafRefs,
Str=DmdType m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
@@ -106,7 +106,7 @@ T7360.$tc'Foo4 = GHC.Types.TrNameS "'Foo1"#
-- RHS size: {terms: 5, types: 0, coercions: 0}
T7360.$tc'Foo1 :: GHC.Types.TyCon
-[GblId[ReflectionId],
+[GblId,
Caf=NoCafRefs,
Str=DmdType m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
@@ -129,7 +129,7 @@ T7360.$tcFoo1 = GHC.Types.TrNameS "Foo"#
-- RHS size: {terms: 5, types: 0, coercions: 0}
T7360.$tcFoo :: GHC.Types.TyCon
-[GblId[ReflectionId],
+[GblId,
Caf=NoCafRefs,
Str=DmdType m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
diff --git a/testsuite/tests/simplCore/should_compile/T9400.stderr b/testsuite/tests/simplCore/should_compile/T9400.stderr
index 8fdcf39711..996890ff94 100644
--- a/testsuite/tests/simplCore/should_compile/T9400.stderr
+++ b/testsuite/tests/simplCore/should_compile/T9400.stderr
@@ -14,7 +14,7 @@ a1 = GHC.Types.TrNameS "T9400"#
-- RHS size: {terms: 3, types: 0, coercions: 0}
T9400.$trModule :: Module
-[GblId[ReflectionId], Caf=NoCafRefs, Str=DmdType]
+[GblId, Caf=NoCafRefs, Str=DmdType]
T9400.$trModule = GHC.Types.Module a a1
-- RHS size: {terms: 22, types: 15, coercions: 0}
diff --git a/testsuite/tests/simplCore/should_compile/spec-inline.stderr b/testsuite/tests/simplCore/should_compile/spec-inline.stderr
index c19aef0555..41824247d7 100644
--- a/testsuite/tests/simplCore/should_compile/spec-inline.stderr
+++ b/testsuite/tests/simplCore/should_compile/spec-inline.stderr
@@ -22,7 +22,7 @@ Roman.$trModule1 = GHC.Types.TrNameS "Roman"#
-- RHS size: {terms: 3, types: 0, coercions: 0}
Roman.$trModule :: GHC.Types.Module
-[GblId[ReflectionId],
+[GblId,
Caf=NoCafRefs,
Str=DmdType m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
diff --git a/testsuite/tests/typecheck/should_compile/tc231.stderr b/testsuite/tests/typecheck/should_compile/tc231.stderr
index 85ccc32954..8c35af42cb 100644
--- a/testsuite/tests/typecheck/should_compile/tc231.stderr
+++ b/testsuite/tests/typecheck/should_compile/tc231.stderr
@@ -1,8 +1,12 @@
TYPE SIGNATURES
+ Node :: forall s a chain. s -> a -> chain -> Q s a chain
+ Z :: forall a. a -> Z a
foo ::
forall s b chain.
Zork s (Z [Char]) b =>
Q s (Z [Char]) chain -> ST s ()
+ huh ::
+ forall s a b. Zork s a b => forall chain. Q s a chain -> ST s ()
s :: forall t t1. Q t (Z [Char]) t1 -> Q t (Z [Char]) t1
TYPE CONSTRUCTORS
data Q s a chain = Node s a chain
@@ -13,9 +17,9 @@ TYPE CONSTRUCTORS
huh :: Q s a chain -> ST s ()
{-# MINIMAL huh #-}
COERCION AXIOMS
- axiom NTCo:Zork ::
+ axiom N:Zork ::
Zork s a b = forall chain. Q s a chain -> ST s ()
-- Defined at tc231.hs:25:1
Dependent modules: []
Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0,
- integer-gmp-1.0.0.0]
+ integer-gmp-1.0.0.1]