summaryrefslogtreecommitdiff
path: root/compiler/GHC/Tc/Deriv/Generate.hs
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/GHC/Tc/Deriv/Generate.hs')
-rw-r--r--compiler/GHC/Tc/Deriv/Generate.hs23
1 files changed, 11 insertions, 12 deletions
diff --git a/compiler/GHC/Tc/Deriv/Generate.hs b/compiler/GHC/Tc/Deriv/Generate.hs
index 33c0765c69..a2ba8d1dbb 100644
--- a/compiler/GHC/Tc/Deriv/Generate.hs
+++ b/compiler/GHC/Tc/Deriv/Generate.hs
@@ -596,7 +596,9 @@ unliftedCompare lt_op eq_op a_expr b_expr lt eq gt
-- mean more tests (dynamically)
nlHsIf (ascribeBool $ genPrimOpApp a_expr eq_op b_expr) eq gt
where
- ascribeBool e = nlExprWithTySig e $ nlHsTyVar boolTyCon_RDR
+ ascribeBool e = noLoc $ ExprWithTySig noExtField e
+ $ mkHsWildCardBndrs $ noLoc $ mkHsImplicitSigType
+ $ nlHsTyVar boolTyCon_RDR
nlConWildPat :: DataCon -> LPat GhcPs
-- The pattern (K {})
@@ -1890,7 +1892,7 @@ gen_Newtype_binds loc cls inst_tvs inst_tys rhs_ty
--
-- op :: forall c. a -> [T x] -> c -> Int
L loc $ ClassOpSig noExtField False [loc_meth_RDR]
- $ mkLHsSigType $ nlHsCoreTy to_ty
+ $ L loc $ mkHsImplicitSigType $ nlHsCoreTy to_ty
)
where
Pair from_ty to_ty = mkCoerceClassMethEqn cls inst_tvs inst_tys rhs_ty meth_id
@@ -1948,11 +1950,6 @@ nlHsAppType e s = noLoc (HsAppType noExtField e hs_ty)
where
hs_ty = mkHsWildCardBndrs $ parenthesizeHsType appPrec $ nlHsCoreTy s
-nlExprWithTySig :: LHsExpr GhcPs -> LHsType GhcPs -> LHsExpr GhcPs
-nlExprWithTySig e s = noLoc $ ExprWithTySig noExtField (parenthesizeHsExpr sigPrec e) hs_ty
- where
- hs_ty = mkLHsSigWcType s
-
nlHsCoreTy :: Type -> LHsType GhcPs
nlHsCoreTy = noLoc . XHsType . NHsCoreTy
@@ -2082,19 +2079,21 @@ genAuxBindSpecDup loc original_rdr_name dup_spec
genAuxBindSpecSig :: SrcSpan -> AuxBindSpec -> LHsSigWcType GhcPs
genAuxBindSpecSig loc spec = case spec of
DerivCon2Tag tycon _
- -> mkLHsSigWcType $ L loc $ XHsType $ NHsCoreTy $
+ -> mk_sig $ L loc $ XHsType $ NHsCoreTy $
mkSpecSigmaTy (tyConTyVars tycon) (tyConStupidTheta tycon) $
mkParentType tycon `mkVisFunTyMany` intPrimTy
DerivTag2Con tycon _
- -> mkLHsSigWcType $ L loc $
+ -> mk_sig $ L loc $
XHsType $ NHsCoreTy $ mkSpecForAllTys (tyConTyVars tycon) $
intTy `mkVisFunTyMany` mkParentType tycon
DerivMaxTag _ _
- -> mkLHsSigWcType (L loc (XHsType (NHsCoreTy intTy)))
+ -> mk_sig (L loc (XHsType (NHsCoreTy intTy)))
DerivDataDataType _ _ _
- -> mkLHsSigWcType (nlHsTyVar dataType_RDR)
+ -> mk_sig (nlHsTyVar dataType_RDR)
DerivDataConstr _ _ _
- -> mkLHsSigWcType (nlHsTyVar constr_RDR)
+ -> mk_sig (nlHsTyVar constr_RDR)
+ where
+ mk_sig = mkHsWildCardBndrs . L loc . mkHsImplicitSigType
type SeparateBagsDerivStuff =
-- DerivAuxBinds