1 {-# LANGUAGE PatternSynonyms, GADTs #-}
5 The following four pattern synonym declarations should give valid
9 -- Check if we mention no explicit type signature (or the correct
10 -- signature "Eq a => Maybe a")
11 pattern Pat1
:: Eq a
=> Maybe a
12 pattern Pat1
<- Just
42
14 -- Check if we mention no explicit type signature (or the correct
15 -- signature "forall b. () => forall a. b ~ Bool => a -> b -> (b, T)")
16 data T
where MkT
:: a
-> T
17 pattern Pat2
:: () => b ~
Bool => a
-> b
-> (b
, T
)
18 pattern Pat2 x y
= (y
, MkT x
)
20 -- Check if we do not tell the user that we could not deduce (Show a)
21 -- from the "required" context. Also, check if we do not give the
22 -- possible fix that suggests to add (Show a) to the "required" context.
23 pattern Pat3
:: Eq a
=> Show a
=> a
-> Maybe a
24 pattern Pat3 x
<- Just x
26 -- Check if we return a valid error message concerning the missing
27 -- constraint (Num a) when the bidirectional pattern synonym is used
28 -- in an expression context
29 data S a
where MkS
:: (Num a
, Show a
) => a
-> S a
30 pattern Pat4
:: (Eq a
) => (Show a
) => S a