1{- 2(c) The University of Glasgow 2006 3(c) The GRASP/AQUA Project, Glasgow University, 1992-1998 4 5 6Pattern-matching constructors 7-} 8 9{-# LANGUAGE CPP #-} 10{-# LANGUAGE TypeFamilies #-} 11{-# LANGUAGE ViewPatterns #-} 12 13module MatchCon ( matchConFamily, matchPatSyn ) where 14 15#include "HsVersions.h" 16 17import GhcPrelude 18 19import {-# SOURCE #-} Match ( match ) 20 21import GHC.Hs 22import DsBinds 23import ConLike 24import BasicTypes ( Origin(..) ) 25import TcType 26import DsMonad 27import DsUtils 28import MkCore ( mkCoreLets ) 29import Util 30import Id 31import NameEnv 32import FieldLabel ( flSelector ) 33import SrcLoc 34import Outputable 35import Control.Monad(liftM) 36import Data.List (groupBy) 37 38{- 39We are confronted with the first column of patterns in a set of 40equations, all beginning with constructors from one ``family'' (e.g., 41@[]@ and @:@ make up the @List@ ``family''). We want to generate the 42alternatives for a @Case@ expression. There are several choices: 43\begin{enumerate} 44\item 45Generate an alternative for every constructor in the family, whether 46they are used in this set of equations or not; this is what the Wadler 47chapter does. 48\begin{description} 49\item[Advantages:] 50(a)~Simple. (b)~It may also be that large sparsely-used constructor 51families are mainly handled by the code for literals. 52\item[Disadvantages:] 53(a)~Not practical for large sparsely-used constructor families, e.g., 54the ASCII character set. (b)~Have to look up a list of what 55constructors make up the whole family. 56\end{description} 57 58\item 59Generate an alternative for each constructor used, then add a default 60alternative in case some constructors in the family weren't used. 61\begin{description} 62\item[Advantages:] 63(a)~Alternatives aren't generated for unused constructors. (b)~The 64STG is quite happy with defaults. (c)~No lookup in an environment needed. 65\item[Disadvantages:] 66(a)~A spurious default alternative may be generated. 67\end{description} 68 69\item 70``Do it right:'' generate an alternative for each constructor used, 71and add a default alternative if all constructors in the family 72weren't used. 73\begin{description} 74\item[Advantages:] 75(a)~You will get cases with only one alternative (and no default), 76which should be amenable to optimisation. Tuples are a common example. 77\item[Disadvantages:] 78(b)~Have to look up constructor families in TDE (as above). 79\end{description} 80\end{enumerate} 81 82We are implementing the ``do-it-right'' option for now. The arguments 83to @matchConFamily@ are the same as to @match@; the extra @Int@ 84returned is the number of constructors in the family. 85 86The function @matchConFamily@ is concerned with this 87have-we-used-all-the-constructors? question; the local function 88@match_cons_used@ does all the real work. 89-} 90 91matchConFamily :: [Id] 92 -> Type 93 -> [[EquationInfo]] 94 -> DsM MatchResult 95-- Each group of eqns is for a single constructor 96matchConFamily (var:vars) ty groups 97 = do alts <- mapM (fmap toRealAlt . matchOneConLike vars ty) groups 98 return (mkCoAlgCaseMatchResult var ty alts) 99 where 100 toRealAlt alt = case alt_pat alt of 101 RealDataCon dcon -> alt{ alt_pat = dcon } 102 _ -> panic "matchConFamily: not RealDataCon" 103matchConFamily [] _ _ = panic "matchConFamily []" 104 105matchPatSyn :: [Id] 106 -> Type 107 -> [EquationInfo] 108 -> DsM MatchResult 109matchPatSyn (var:vars) ty eqns 110 = do alt <- fmap toSynAlt $ matchOneConLike vars ty eqns 111 return (mkCoSynCaseMatchResult var ty alt) 112 where 113 toSynAlt alt = case alt_pat alt of 114 PatSynCon psyn -> alt{ alt_pat = psyn } 115 _ -> panic "matchPatSyn: not PatSynCon" 116matchPatSyn _ _ _ = panic "matchPatSyn []" 117 118type ConArgPats = HsConDetails (LPat GhcTc) (HsRecFields GhcTc (LPat GhcTc)) 119 120matchOneConLike :: [Id] 121 -> Type 122 -> [EquationInfo] 123 -> DsM (CaseAlt ConLike) 124matchOneConLike vars ty (eqn1 : eqns) -- All eqns for a single constructor 125 = do { let inst_tys = ASSERT( all tcIsTcTyVar ex_tvs ) 126 -- ex_tvs can only be tyvars as data types in source 127 -- Haskell cannot mention covar yet (Aug 2018). 128 ASSERT( tvs1 `equalLength` ex_tvs ) 129 arg_tys ++ mkTyVarTys tvs1 130 131 val_arg_tys = conLikeInstOrigArgTys con1 inst_tys 132 -- dataConInstOrigArgTys takes the univ and existential tyvars 133 -- and returns the types of the *value* args, which is what we want 134 135 match_group :: [Id] 136 -> [(ConArgPats, EquationInfo)] -> DsM MatchResult 137 -- All members of the group have compatible ConArgPats 138 match_group arg_vars arg_eqn_prs 139 = ASSERT( notNull arg_eqn_prs ) 140 do { (wraps, eqns') <- liftM unzip (mapM shift arg_eqn_prs) 141 ; let group_arg_vars = select_arg_vars arg_vars arg_eqn_prs 142 ; match_result <- match (group_arg_vars ++ vars) ty eqns' 143 ; return (adjustMatchResult (foldr1 (.) wraps) match_result) } 144 145 shift (_, eqn@(EqnInfo { eqn_pats = ConPatOut{ pat_tvs = tvs, pat_dicts = ds, 146 pat_binds = bind, pat_args = args 147 } : pats })) 148 = do ds_bind <- dsTcEvBinds bind 149 return ( wrapBinds (tvs `zip` tvs1) 150 . wrapBinds (ds `zip` dicts1) 151 . mkCoreLets ds_bind 152 , eqn { eqn_orig = Generated 153 , eqn_pats = conArgPats val_arg_tys args ++ pats } 154 ) 155 shift (_, (EqnInfo { eqn_pats = ps })) = pprPanic "matchOneCon/shift" (ppr ps) 156 157 ; arg_vars <- selectConMatchVars val_arg_tys args1 158 -- Use the first equation as a source of 159 -- suggestions for the new variables 160 161 -- Divide into sub-groups; see Note [Record patterns] 162 ; let groups :: [[(ConArgPats, EquationInfo)]] 163 groups = groupBy compatible_pats [ (pat_args (firstPat eqn), eqn) 164 | eqn <- eqn1:eqns ] 165 166 ; match_results <- mapM (match_group arg_vars) groups 167 168 ; return $ MkCaseAlt{ alt_pat = con1, 169 alt_bndrs = tvs1 ++ dicts1 ++ arg_vars, 170 alt_wrapper = wrapper1, 171 alt_result = foldr1 combineMatchResults match_results } } 172 where 173 ConPatOut { pat_con = (dL->L _ con1) 174 , pat_arg_tys = arg_tys, pat_wrap = wrapper1, 175 pat_tvs = tvs1, pat_dicts = dicts1, pat_args = args1 } 176 = firstPat eqn1 177 fields1 = map flSelector (conLikeFieldLabels con1) 178 179 ex_tvs = conLikeExTyCoVars con1 180 181 -- Choose the right arg_vars in the right order for this group 182 -- Note [Record patterns] 183 select_arg_vars :: [Id] -> [(ConArgPats, EquationInfo)] -> [Id] 184 select_arg_vars arg_vars ((arg_pats, _) : _) 185 | RecCon flds <- arg_pats 186 , let rpats = rec_flds flds 187 , not (null rpats) -- Treated specially; cf conArgPats 188 = ASSERT2( fields1 `equalLength` arg_vars, 189 ppr con1 $$ ppr fields1 $$ ppr arg_vars ) 190 map lookup_fld rpats 191 | otherwise 192 = arg_vars 193 where 194 fld_var_env = mkNameEnv $ zipEqual "get_arg_vars" fields1 arg_vars 195 lookup_fld (dL->L _ rpat) = lookupNameEnv_NF fld_var_env 196 (idName (unLoc (hsRecFieldId rpat))) 197 select_arg_vars _ [] = panic "matchOneCon/select_arg_vars []" 198matchOneConLike _ _ [] = panic "matchOneCon []" 199 200----------------- 201compatible_pats :: (ConArgPats,a) -> (ConArgPats,a) -> Bool 202-- Two constructors have compatible argument patterns if the number 203-- and order of sub-matches is the same in both cases 204compatible_pats (RecCon flds1, _) (RecCon flds2, _) = same_fields flds1 flds2 205compatible_pats (RecCon flds1, _) _ = null (rec_flds flds1) 206compatible_pats _ (RecCon flds2, _) = null (rec_flds flds2) 207compatible_pats _ _ = True -- Prefix or infix con 208 209same_fields :: HsRecFields GhcTc (LPat GhcTc) -> HsRecFields GhcTc (LPat GhcTc) 210 -> Bool 211same_fields flds1 flds2 212 = all2 (\(dL->L _ f1) (dL->L _ f2) 213 -> unLoc (hsRecFieldId f1) == unLoc (hsRecFieldId f2)) 214 (rec_flds flds1) (rec_flds flds2) 215 216 217----------------- 218selectConMatchVars :: [Type] -> ConArgPats -> DsM [Id] 219selectConMatchVars arg_tys (RecCon {}) = newSysLocalsDsNoLP arg_tys 220selectConMatchVars _ (PrefixCon ps) = selectMatchVars (map unLoc ps) 221selectConMatchVars _ (InfixCon p1 p2) = selectMatchVars [unLoc p1, unLoc p2] 222 223conArgPats :: [Type] -- Instantiated argument types 224 -- Used only to fill in the types of WildPats, which 225 -- are probably never looked at anyway 226 -> ConArgPats 227 -> [Pat GhcTc] 228conArgPats _arg_tys (PrefixCon ps) = map unLoc ps 229conArgPats _arg_tys (InfixCon p1 p2) = [unLoc p1, unLoc p2] 230conArgPats arg_tys (RecCon (HsRecFields { rec_flds = rpats })) 231 | null rpats = map WildPat arg_tys 232 -- Important special case for C {}, which can be used for a 233 -- datacon that isn't declared to have fields at all 234 | otherwise = map (unLoc . hsRecFieldArg . unLoc) rpats 235 236{- 237Note [Record patterns] 238~~~~~~~~~~~~~~~~~~~~~~ 239Consider 240 data T = T { x,y,z :: Bool } 241 242 f (T { y=True, x=False }) = ... 243 244We must match the patterns IN THE ORDER GIVEN, thus for the first 245one we match y=True before x=False. See #246; or imagine 246matching against (T { y=False, x=undefined }): should fail without 247touching the undefined. 248 249Now consider: 250 251 f (T { y=True, x=False }) = ... 252 f (T { x=True, y= False}) = ... 253 254In the first we must test y first; in the second we must test x 255first. So we must divide even the equations for a single constructor 256T into sub-goups, based on whether they match the same field in the 257same order. That's what the (groupBy compatible_pats) grouping. 258 259All non-record patterns are "compatible" in this sense, because the 260positional patterns (T a b) and (a `T` b) all match the arguments 261in order. Also T {} is special because it's equivalent to (T _ _). 262Hence the (null rpats) checks here and there. 263 264 265Note [Existentials in shift_con_pat] 266~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 267Consider 268 data T = forall a. Ord a => T a (a->Int) 269 270 f (T x f) True = ...expr1... 271 f (T y g) False = ...expr2.. 272 273When we put in the tyvars etc we get 274 275 f (T a (d::Ord a) (x::a) (f::a->Int)) True = ...expr1... 276 f (T b (e::Ord b) (y::a) (g::a->Int)) True = ...expr2... 277 278After desugaring etc we'll get a single case: 279 280 f = \t::T b::Bool -> 281 case t of 282 T a (d::Ord a) (x::a) (f::a->Int)) -> 283 case b of 284 True -> ...expr1... 285 False -> ...expr2... 286 287*** We have to substitute [a/b, d/e] in expr2! ** 288Hence 289 False -> ....((/\b\(e:Ord b).expr2) a d).... 290 291Originally I tried to use 292 (\b -> let e = d in expr2) a 293to do this substitution. While this is "correct" in a way, it fails 294Lint, because e::Ord b but d::Ord a. 295 296-} 297