Skip to content
Snippets Groups Projects
Commit cbedd1ce authored by Simon Peyton Jones's avatar Simon Peyton Jones Committed by pcapriotti
Browse files

Two small fixes to SpecConstr for functions with equality-proof args

First, make Rules.match_co able to deal wit some modest coercions
Second, make SpecConstr use wild-card for coercion arguments

This is the rest of the fix for Trac #7165

MERGED from commit b04ff2fe
parent 87511d1c
No related branches found
No related tags found
No related merge requests found
......@@ -725,8 +725,13 @@ match_co :: RuleEnv
-> Maybe RuleSubst
match_co renv subst (CoVarCo cv) co
= match_var renv subst cv (Coercion co)
match_co renv subst (Refl ty1) co
= case co of
Refl ty2 -> match_ty renv subst ty1 ty2
_ -> Nothing
match_co _ _ co1 _
= pprTrace "match_co bailing out" (ppr co1) Nothing
= pprTrace "match_co: needs more cases" (ppr co1) Nothing
-- Currently just deals with CoVarCo and Refl
-------------
rnMatchBndr2 :: RuleEnv -> RuleSubst -> Var -> Var -> RuleEnv
......
......@@ -1585,9 +1585,6 @@ argToPat :: ScEnv
argToPat _env _in_scope _val_env arg@(Type {}) _arg_occ
= return (False, arg)
argToPat _env _in_scope _val_env arg@(Coercion {}) _arg_occ
= return (False, arg)
argToPat env in_scope val_env (Tick _ arg) arg_occ
= argToPat env in_scope val_env arg arg_occ
-- Note [Notes in call patterns]
......@@ -1696,6 +1693,7 @@ argToPat env in_scope val_env (Var v) arg_occ
-- We don't want to specialise for that *particular* x,y
-- The default case: make a wild-card
-- We use this for coercions too
argToPat _env _in_scope _val_env arg _arg_occ
= wildCardPat (exprType arg)
......@@ -1703,7 +1701,7 @@ wildCardPat :: Type -> UniqSM (Bool, CoreArg)
wildCardPat ty
= do { uniq <- getUniqueUs
; let id = mkSysLocal (fsLit "sc") uniq ty
; return (False, Var id) }
; return (False, varToCoreExpr id) }
argsToPats :: ScEnv -> InScopeSet -> ValueEnv
-> [CoreArg] -> [ArgOcc] -- Should be same length
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment