summaryrefslogtreecommitdiff
path: root/compiler/deSugar/MatchCon.hs
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/deSugar/MatchCon.hs')
-rw-r--r--compiler/deSugar/MatchCon.hs8
1 files changed, 5 insertions, 3 deletions
diff --git a/compiler/deSugar/MatchCon.hs b/compiler/deSugar/MatchCon.hs
index 47d1276ba6..7923ae4eb5 100644
--- a/compiler/deSugar/MatchCon.hs
+++ b/compiler/deSugar/MatchCon.hs
@@ -7,6 +7,7 @@ Pattern-matching constructors
-}
{-# LANGUAGE CPP #-}
+{-# LANGUAGE TypeFamilies #-}
module MatchCon ( matchConFamily, matchPatSyn ) where
@@ -112,7 +113,7 @@ matchPatSyn (var:vars) ty eqns
_ -> panic "matchPatSyn: not PatSynCon"
matchPatSyn _ _ _ = panic "matchPatSyn []"
-type ConArgPats = HsConDetails (LPat Id) (HsRecFields Id (LPat Id))
+type ConArgPats = HsConDetails (LPat GhcTc) (HsRecFields GhcTc (LPat GhcTc))
matchOneConLike :: [Id]
-> Type
@@ -198,7 +199,8 @@ compatible_pats (RecCon flds1, _) _ = null (rec_flds flds1)
compatible_pats _ (RecCon flds2, _) = null (rec_flds flds2)
compatible_pats _ _ = True -- Prefix or infix con
-same_fields :: HsRecFields Id (LPat Id) -> HsRecFields Id (LPat Id) -> Bool
+same_fields :: HsRecFields GhcTc (LPat GhcTc) -> HsRecFields GhcTc (LPat GhcTc)
+ -> Bool
same_fields flds1 flds2
= all2 (\(L _ f1) (L _ f2)
-> unLoc (hsRecFieldId f1) == unLoc (hsRecFieldId f2))
@@ -215,7 +217,7 @@ conArgPats :: [Type] -- Instantiated argument types
-- Used only to fill in the types of WildPats, which
-- are probably never looked at anyway
-> ConArgPats
- -> [Pat Id]
+ -> [Pat GhcTc]
conArgPats _arg_tys (PrefixCon ps) = map unLoc ps
conArgPats _arg_tys (InfixCon p1 p2) = [unLoc p1, unLoc p2]
conArgPats arg_tys (RecCon (HsRecFields { rec_flds = rpats }))