never executed always true always false
1 {-# LANGUAGE TypeApplications #-}
2
3 -- | COMPLETE signature
4 module GHC.Types.CompleteMatch where
5
6 import GHC.Prelude
7 import GHC.Core.TyCo.Rep
8 import GHC.Types.Unique.DSet
9 import GHC.Core.ConLike
10 import GHC.Core.TyCon
11 import GHC.Core.Type ( splitTyConApp_maybe )
12 import GHC.Utils.Outputable
13
14 -- | A list of conlikes which represents a complete pattern match.
15 -- These arise from @COMPLETE@ signatures.
16 -- See also Note [Implementation of COMPLETE pragmas].
17 data CompleteMatch = CompleteMatch
18 { cmConLikes :: UniqDSet ConLike -- ^ The set of `ConLike` values
19 , cmResultTyCon :: Maybe TyCon -- ^ The optional, concrete result TyCon the set applies to
20 }
21
22 vanillaCompleteMatch :: UniqDSet ConLike -> CompleteMatch
23 vanillaCompleteMatch cls = CompleteMatch { cmConLikes = cls, cmResultTyCon = Nothing }
24
25 instance Outputable CompleteMatch where
26 ppr (CompleteMatch cls mty) = case mty of
27 Nothing -> ppr cls
28 Just ty -> ppr cls <> text "@" <> parens (ppr ty)
29
30 type CompleteMatches = [CompleteMatch]
31
32 completeMatchAppliesAtType :: Type -> CompleteMatch -> Bool
33 completeMatchAppliesAtType ty cm = all @Maybe ty_matches (cmResultTyCon cm)
34 where
35 ty_matches sig_tc
36 | Just (tc, _arg_tys) <- splitTyConApp_maybe ty
37 , tc == sig_tc
38 = True
39 | otherwise
40 = False