summaryrefslogtreecommitdiff
path: root/compiler/hieFile
diff options
context:
space:
mode:
authorSimon Peyton Jones <simonpj@microsoft.com>2019-02-15 09:53:48 +0000
committerMarge Bot <ben+marge-bot@smart-cactus.org>2019-02-23 21:31:47 -0500
commit6cce36f83aec33d33545e0ef2135894d22dff5ca (patch)
tree3bfa83e7ba313f7a10b9219cb58eb18a8d368b2d /compiler/hieFile
parentac34e784775a0fa8b7284d42ff89571907afdc36 (diff)
downloadhaskell-6cce36f83aec33d33545e0ef2135894d22dff5ca.tar.gz
Add AnonArgFlag to FunTy
The big payload of this patch is: Add an AnonArgFlag to the FunTy constructor of Type, so that (FunTy VisArg t1 t2) means (t1 -> t2) (FunTy InvisArg t1 t2) means (t1 => t2) The big payoff is that we have a simple, local test to make when decomposing a type, leading to many fewer calls to isPredTy. To me the code seems a lot tidier, and probably more efficient (isPredTy has to take the kind of the type). See Note [Function types] in TyCoRep. There are lots of consequences * I made FunTy into a record, so that it'll be easier when we add a linearity field, something that is coming down the road. * Lots of code gets touched in a routine way, simply because it pattern matches on FunTy. * I wanted to make a pattern synonym for (FunTy2 arg res), which picks out just the argument and result type from the record. But alas the pattern-match overlap checker has a heart attack, and either reports false positives, or takes too long. In the end I gave up on pattern synonyms. There's some commented-out code in TyCoRep that shows what I wanted to do. * Much more clarity about predicate types, constraint types and (in particular) equality constraints in kinds. See TyCoRep Note [Types for coercions, predicates, and evidence] and Note [Constraints in kinds]. This made me realise that we need an AnonArgFlag on AnonTCB in a TyConBinder, something that was really plain wrong before. See TyCon Note [AnonTCB InivsArg] * When building function types we must know whether we need VisArg (mkVisFunTy) or InvisArg (mkInvisFunTy). This turned out to be pretty easy in practice. * Pretty-printing of types, esp in IfaceType, gets tidier, because we were already recording the (->) vs (=>) distinction in an ad-hoc way. Death to IfaceFunTy. * mkLamType needs to keep track of whether it is building (t1 -> t2) or (t1 => t2). See Type Note [mkLamType: dictionary arguments] Other minor stuff * Some tidy-up in validity checking involving constraints; Trac #16263
Diffstat (limited to 'compiler/hieFile')
-rw-r--r--compiler/hieFile/HieAst.hs4
-rw-r--r--compiler/hieFile/HieUtils.hs14
2 files changed, 9 insertions, 9 deletions
diff --git a/compiler/hieFile/HieAst.hs b/compiler/hieFile/HieAst.hs
index 7fd217cda5..9ac65ce399 100644
--- a/compiler/hieFile/HieAst.hs
+++ b/compiler/hieFile/HieAst.hs
@@ -31,7 +31,7 @@ import Name ( Name, nameSrcSpan, setNameLoc )
import NameEnv ( NameEnv, emptyNameEnv, extendNameEnv, lookupNameEnv )
import SrcLoc
import TcHsSyn ( hsLitType, hsPatType )
-import Type ( mkFunTys, Type )
+import Type ( mkVisFunTys, Type )
import TysWiredIn ( mkListTy, mkSumTy )
import Var ( Id, Var, setVarName, varName, varType )
import TcRnTypes
@@ -488,7 +488,7 @@ instance HasType (LHsExpr GhcTc) where
fallback = makeNode e' spn
matchGroupType :: MatchGroupTc -> Type
- matchGroupType (MatchGroupTc args res) = mkFunTys args res
+ matchGroupType (MatchGroupTc args res) = mkVisFunTys args res
-- | Skip desugaring of these expressions for performance reasons.
--
diff --git a/compiler/hieFile/HieUtils.hs b/compiler/hieFile/HieUtils.hs
index 5259ea1280..9231317bd0 100644
--- a/compiler/hieFile/HieUtils.hs
+++ b/compiler/hieFile/HieUtils.hs
@@ -63,7 +63,7 @@ resolveVisibility kind ty_args
where
ts' = go (extendTvSubst env tv t) res ts
- go env (FunTy _ res) (t:ts) -- No type-class args in tycon apps
+ go env (FunTy { ft_res = res }) (t:ts) -- No type-class args in tycon apps
= (True,t) : (go env res ts)
go env (TyVarTy tv) ts
@@ -81,8 +81,8 @@ hieTypeToIface = foldType go
go (HLitTy l) = IfaceLitTy l
go (HForAllTy ((n,k),af) t) = let b = (occNameFS $ getOccName n, k)
in IfaceForAllTy (Bndr (IfaceTvBndr b) af) t
- go (HFunTy a b) = IfaceFunTy a b
- go (HQualTy pred b) = IfaceDFunTy pred b
+ go (HFunTy a b) = IfaceFunTy VisArg a b
+ go (HQualTy pred b) = IfaceFunTy InvisArg pred b
go (HCastTy a) = a
go HCoercionTy = IfaceTyVar "<coercion type>"
go (HTyConApp a xs) = IfaceTyConApp a (hieToIfaceArgs xs)
@@ -158,12 +158,12 @@ getTypeIndex t
k <- getTypeIndex (varType v)
i <- getTypeIndex t
return $ HForAllTy ((varName v,k),a) i
- go (FunTy a b) = do
+ go (FunTy { ft_af = af, ft_arg = a, ft_res = b }) = do
ai <- getTypeIndex a
bi <- getTypeIndex b
- return $ if isPredTy a
- then HQualTy ai bi
- else HFunTy ai bi
+ return $ case af of
+ InvisArg -> HQualTy ai bi
+ VisArg -> HFunTy ai bi
go (LitTy a) = return $ HLitTy $ toIfaceTyLit a
go (CastTy t _) = do
i <- getTypeIndex t