diff options
author | Alan Zimmerman <alan.zimm@gmail.com> | 2020-02-17 19:28:10 +0000 |
---|---|---|
committer | Alan Zimmerman <alan.zimm@gmail.com> | 2020-02-18 19:28:31 +0000 |
commit | 2d017369b1e9e0640911315e469bae3d190b83e2 (patch) | |
tree | 6260249dbd5a1f6edc658916e76a29f048b80dbb | |
parent | ee1e5342f612c8b06ac910cd698558ade7a1a887 (diff) | |
download | haskell-wip/T17842-ppr-hscase.tar.gz |
Reduce braces in pretty printing HsCasewip/T17842-ppr-hscase
Only use braces when printing an empty case statement, so
case z of { }
Closes #17842
24 files changed, 90 insertions, 85 deletions
diff --git a/compiler/GHC/Hs/Expr.hs b/compiler/GHC/Hs/Expr.hs index 6890484472..f414cde550 100644 --- a/compiler/GHC/Hs/Expr.hs +++ b/compiler/GHC/Hs/Expr.hs @@ -1009,12 +1009,13 @@ ppr_expr (HsLamCase _ matches) = sep [ sep [text "\\case"], nest 2 (pprMatches matches) ] -ppr_expr (HsCase _ expr matches@(MG { mg_alts = L _ [_] })) - = sep [ sep [text "case", nest 4 (ppr expr), ptext (sLit "of {")], - nest 2 (pprMatches matches) <+> char '}'] -ppr_expr (HsCase _ expr matches) +ppr_expr (HsCase _ expr matches@(MG { mg_alts = L _ alts })) = sep [ sep [text "case", nest 4 (ppr expr), ptext (sLit "of")], - nest 2 (pprMatches matches) ] + pp_alts ] + where + pp_alts | null alts = text "{}" + | otherwise = nest 2 (pprMatches matches) +ppr_expr (HsCase _ _ (XMatchGroup nec)) = noExtCon nec ppr_expr (HsIf _ _ e1 e2 e3) = sep [hsep [text "if", nest 2 (ppr e1), ptext (sLit "then")], diff --git a/testsuite/tests/deriving/should_compile/T14682.stderr b/testsuite/tests/deriving/should_compile/T14682.stderr index 59fc405cdb..b7e2793451 100644 --- a/testsuite/tests/deriving/should_compile/T14682.stderr +++ b/testsuite/tests/deriving/should_compile/T14682.stderr @@ -33,23 +33,23 @@ Derived class instances: instance GHC.Classes.Ord T14682.Foo where GHC.Classes.compare a b - = case a of { + = case a of T14682.Foo a1 a2 - -> case b of { + -> case b of T14682.Foo b1 b2 -> case (GHC.Classes.compare a1 b1) of GHC.Types.LT -> GHC.Types.LT GHC.Types.EQ -> (a2 `GHC.Classes.compare` b2) - GHC.Types.GT -> GHC.Types.GT } } + GHC.Types.GT -> GHC.Types.GT (GHC.Classes.<) a b - = case a of { + = case a of T14682.Foo a1 a2 - -> case b of { + -> case b of T14682.Foo b1 b2 -> case (GHC.Classes.compare a1 b1) of GHC.Types.LT -> GHC.Types.True GHC.Types.EQ -> (a2 GHC.Classes.< b2) - GHC.Types.GT -> GHC.Types.False } } + GHC.Types.GT -> GHC.Types.False (GHC.Classes.<=) a b = GHC.Classes.not ((GHC.Classes.<) b a) (GHC.Classes.>) a b = (GHC.Classes.<) b a (GHC.Classes.>=) a b = GHC.Classes.not ((GHC.Classes.<) a b) diff --git a/testsuite/tests/deriving/should_compile/drv-empty-data.stderr b/testsuite/tests/deriving/should_compile/drv-empty-data.stderr index d6e4eee4b0..815963bb4f 100644 --- a/testsuite/tests/deriving/should_compile/drv-empty-data.stderr +++ b/testsuite/tests/deriving/should_compile/drv-empty-data.stderr @@ -7,7 +7,7 @@ Derived class instances: GHC.Read.readListPrec = GHC.Read.readListPrecDefault instance GHC.Show.Show (DrvEmptyData.Void a) where - GHC.Show.showsPrec _ z = case z of + GHC.Show.showsPrec _ z = case z of {} instance GHC.Classes.Ord (DrvEmptyData.Void a) where GHC.Classes.compare _ z = GHC.Types.EQ @@ -17,36 +17,37 @@ Derived class instances: instance Data.Data.Data a => Data.Data.Data (DrvEmptyData.Void a) where - Data.Data.gfoldl _ _ z = case z of - Data.Data.gunfold k z c = case Data.Data.constrIndex c of - Data.Data.toConstr z = case z of + Data.Data.gfoldl _ _ z = case z of {} + Data.Data.gunfold k z c = case Data.Data.constrIndex c of {} + Data.Data.toConstr z = case z of {} Data.Data.dataTypeOf _ = DrvEmptyData.$tVoid Data.Data.dataCast1 f = Data.Typeable.gcast1 f instance GHC.Base.Functor DrvEmptyData.Void where - GHC.Base.fmap _ z = case z of - (GHC.Base.<$) _ z = case z of + GHC.Base.fmap _ z = case z of {} + (GHC.Base.<$) _ z = case z of {} instance Data.Foldable.Foldable DrvEmptyData.Void where Data.Foldable.foldMap _ z = GHC.Base.mempty instance Data.Traversable.Traversable DrvEmptyData.Void where - Data.Traversable.traverse _ z = GHC.Base.pure (case z of) + Data.Traversable.traverse _ z = GHC.Base.pure (case z of {}) instance GHC.Generics.Generic (DrvEmptyData.Void a) where GHC.Generics.from x - = GHC.Generics.M1 (case x of { x -> case x of }) - GHC.Generics.to (GHC.Generics.M1 x) = case x of { x -> case x of } + = GHC.Generics.M1 (case x of x -> case x of {}) + GHC.Generics.to (GHC.Generics.M1 x) = case x of x -> case x of {} instance GHC.Generics.Generic1 DrvEmptyData.Void where GHC.Generics.from1 x - = GHC.Generics.M1 (case x of { x -> case x of }) - GHC.Generics.to1 (GHC.Generics.M1 x) = case x of { x -> case x of } + = GHC.Generics.M1 (case x of x -> case x of {}) + GHC.Generics.to1 (GHC.Generics.M1 x) = case x of x -> case x of {} instance Language.Haskell.TH.Syntax.Lift (DrvEmptyData.Void a) where - Language.Haskell.TH.Syntax.lift z = GHC.Base.pure (case z of) - Language.Haskell.TH.Syntax.liftTyped z = GHC.Base.pure (case z of) + Language.Haskell.TH.Syntax.lift z = GHC.Base.pure (case z of {}) + Language.Haskell.TH.Syntax.liftTyped z + = GHC.Base.pure (case z of {}) DrvEmptyData.$tVoid :: Data.Data.DataType DrvEmptyData.$tVoid = Data.Data.mkDataType "Void" [] diff --git a/testsuite/tests/gadt/T3169.stderr b/testsuite/tests/gadt/T3169.stderr index d0f650b9ab..4072188882 100644 --- a/testsuite/tests/gadt/T3169.stderr +++ b/testsuite/tests/gadt/T3169.stderr @@ -6,8 +6,8 @@ T3169.hs:13:22: error: • In the second argument of ‘lookup’, namely ‘m’ In the expression: lookup a m :: Maybe (Map b elt) In the expression: - case lookup a m :: Maybe (Map b elt) of { - Just (m2 :: Map b elt) -> lookup b m2 :: Maybe elt } + case lookup a m :: Maybe (Map b elt) of + Just (m2 :: Map b elt) -> lookup b m2 :: Maybe elt • Relevant bindings include m :: Map (a, b) elt (bound at T3169.hs:12:17) b :: b (bound at T3169.hs:12:13) diff --git a/testsuite/tests/gadt/gadt-escape1.stderr b/testsuite/tests/gadt/gadt-escape1.stderr index 41322f9cbc..ff9e82d0e9 100644 --- a/testsuite/tests/gadt/gadt-escape1.stderr +++ b/testsuite/tests/gadt/gadt-escape1.stderr @@ -7,13 +7,14 @@ gadt-escape1.hs:19:58: error: in a case alternative at gadt-escape1.hs:19:43-50 ‘p’ is a rigid type variable bound by - the inferred type of weird1 :: p at gadt-escape1.hs:19:1-58 + the inferred type of weird1 :: p + at gadt-escape1.hs:19:1-58 Possible fix: add a type signature for ‘weird1’ Expected type: p Actual type: ExpGADT t • In the expression: a In a case alternative: Hidden (ExpInt _) a -> a In the expression: - case (hval :: Hidden) of { Hidden (ExpInt _) a -> a } + case (hval :: Hidden) of Hidden (ExpInt _) a -> a • Relevant bindings include weird1 :: p (bound at gadt-escape1.hs:19:1) diff --git a/testsuite/tests/gadt/gadt7.stderr b/testsuite/tests/gadt/gadt7.stderr index bb179975fb..5bd36e39c8 100644 --- a/testsuite/tests/gadt/gadt7.stderr +++ b/testsuite/tests/gadt/gadt7.stderr @@ -7,13 +7,15 @@ gadt7.hs:16:38: error: in a case alternative at gadt7.hs:16:33 ‘p’ is a rigid type variable bound by - the inferred type of i1b :: T a -> p -> p1 at gadt7.hs:16:1-44 + the inferred type of i1b :: T a -> p -> p1 + at gadt7.hs:16:1-44 ‘p1’ is a rigid type variable bound by - the inferred type of i1b :: T a -> p -> p1 at gadt7.hs:16:1-44 + the inferred type of i1b :: T a -> p -> p1 + at gadt7.hs:16:1-44 Possible fix: add a type signature for ‘i1b’ • In the expression: y1 In a case alternative: K -> y1 - In the expression: case t1 of { K -> y1 } + In the expression: case t1 of K -> y1 • Relevant bindings include y1 :: p (bound at gadt7.hs:16:16) y :: p (bound at gadt7.hs:16:7) diff --git a/testsuite/tests/generics/T10604/T10604_deriving.stderr b/testsuite/tests/generics/T10604/T10604_deriving.stderr index 99c5ee8088..933bbecdff 100644 --- a/testsuite/tests/generics/T10604/T10604_deriving.stderr +++ b/testsuite/tests/generics/T10604/T10604_deriving.stderr @@ -93,52 +93,52 @@ Derived class instances: GHC.Generics.Generic (T10604_deriving.Wrap2 @k a) where GHC.Generics.from x = GHC.Generics.M1 - (case x of { + (case x of T10604_deriving.Wrap2 g1 - -> GHC.Generics.M1 (GHC.Generics.M1 (GHC.Generics.K1 g1)) }) + -> GHC.Generics.M1 (GHC.Generics.M1 (GHC.Generics.K1 g1))) GHC.Generics.to (GHC.Generics.M1 x) - = case x of { + = case x of (GHC.Generics.M1 (GHC.Generics.M1 (GHC.Generics.K1 g1))) - -> T10604_deriving.Wrap2 g1 } + -> T10604_deriving.Wrap2 g1 instance GHC.Generics.Generic1 @(k -> *) (T10604_deriving.Wrap2 @k) where GHC.Generics.from1 x = GHC.Generics.M1 - (case x of { + (case x of T10604_deriving.Wrap2 g1 -> GHC.Generics.M1 (GHC.Generics.M1 ((GHC.Base..) - GHC.Generics.Comp1 (GHC.Base.fmap GHC.Generics.Rec1) g1)) }) + GHC.Generics.Comp1 (GHC.Base.fmap GHC.Generics.Rec1) g1))) GHC.Generics.to1 (GHC.Generics.M1 x) - = case x of { + = case x of (GHC.Generics.M1 (GHC.Generics.M1 g1)) -> T10604_deriving.Wrap2 ((GHC.Base..) - (GHC.Base.fmap GHC.Generics.unRec1) GHC.Generics.unComp1 g1) } + (GHC.Base.fmap GHC.Generics.unRec1) GHC.Generics.unComp1 g1) instance GHC.Generics.Generic (T10604_deriving.Wrap a) where GHC.Generics.from x = GHC.Generics.M1 - (case x of { + (case x of T10604_deriving.Wrap g1 - -> GHC.Generics.M1 (GHC.Generics.M1 (GHC.Generics.K1 g1)) }) + -> GHC.Generics.M1 (GHC.Generics.M1 (GHC.Generics.K1 g1))) GHC.Generics.to (GHC.Generics.M1 x) - = case x of { + = case x of (GHC.Generics.M1 (GHC.Generics.M1 (GHC.Generics.K1 g1))) - -> T10604_deriving.Wrap g1 } + -> T10604_deriving.Wrap g1 instance GHC.Generics.Generic1 @(* -> *) T10604_deriving.Wrap where GHC.Generics.from1 x = GHC.Generics.M1 - (case x of { + (case x of T10604_deriving.Wrap g1 - -> GHC.Generics.M1 (GHC.Generics.M1 (GHC.Generics.Rec1 g1)) }) + -> GHC.Generics.M1 (GHC.Generics.M1 (GHC.Generics.Rec1 g1))) GHC.Generics.to1 (GHC.Generics.M1 x) - = case x of { + = case x of (GHC.Generics.M1 (GHC.Generics.M1 g1)) - -> T10604_deriving.Wrap (GHC.Generics.unRec1 g1) } + -> T10604_deriving.Wrap (GHC.Generics.unRec1 g1) instance GHC.Base.Functor (T10604_deriving.Proxy @(*)) where GHC.Base.fmap _ = GHC.Prim.coerce @@ -147,31 +147,31 @@ Derived class instances: GHC.Generics.Generic (T10604_deriving.Proxy @k a) where GHC.Generics.from x = GHC.Generics.M1 - (case x of { - T10604_deriving.Proxy -> GHC.Generics.M1 GHC.Generics.U1 }) + (case x of + T10604_deriving.Proxy -> GHC.Generics.M1 GHC.Generics.U1) GHC.Generics.to (GHC.Generics.M1 x) - = case x of { - (GHC.Generics.M1 GHC.Generics.U1) -> T10604_deriving.Proxy } + = case x of + (GHC.Generics.M1 GHC.Generics.U1) -> T10604_deriving.Proxy instance GHC.Generics.Generic1 @k (T10604_deriving.Proxy @k) where GHC.Generics.from1 x = GHC.Generics.M1 - (case x of { - T10604_deriving.Proxy -> GHC.Generics.M1 GHC.Generics.U1 }) + (case x of + T10604_deriving.Proxy -> GHC.Generics.M1 GHC.Generics.U1) GHC.Generics.to1 (GHC.Generics.M1 x) - = case x of { - (GHC.Generics.M1 GHC.Generics.U1) -> T10604_deriving.Proxy } + = case x of + (GHC.Generics.M1 GHC.Generics.U1) -> T10604_deriving.Proxy instance GHC.Generics.Generic (T10604_deriving.Empty a) where GHC.Generics.from x - = GHC.Generics.M1 (case x of { x -> case x of }) - GHC.Generics.to (GHC.Generics.M1 x) = case x of { x -> case x of } + = GHC.Generics.M1 (case x of x -> case x of {}) + GHC.Generics.to (GHC.Generics.M1 x) = case x of x -> case x of {} instance GHC.Generics.Generic1 @GHC.Types.Bool T10604_deriving.Empty where GHC.Generics.from1 x - = GHC.Generics.M1 (case x of { x -> case x of }) - GHC.Generics.to1 (GHC.Generics.M1 x) = case x of { x -> case x of } + = GHC.Generics.M1 (case x of x -> case x of {}) + GHC.Generics.to1 (GHC.Generics.M1 x) = case x of x -> case x of {} Derived type family instances: diff --git a/testsuite/tests/indexed-types/should_fail/GADTwrong1.stderr b/testsuite/tests/indexed-types/should_fail/GADTwrong1.stderr index 44dc9475c0..46d8c43ddc 100644 --- a/testsuite/tests/indexed-types/should_fail/GADTwrong1.stderr +++ b/testsuite/tests/indexed-types/should_fail/GADTwrong1.stderr @@ -11,7 +11,7 @@ GADTwrong1.hs:12:21: error: at GADTwrong1.hs:10:1-29 • In the expression: y In a case alternative: T y -> y - In the expression: case T x :: T (Const b) of { T y -> y } + In the expression: case T x :: T (Const b) of T y -> y • Relevant bindings include y :: c (bound at GADTwrong1.hs:12:16) coerce :: a -> b (bound at GADTwrong1.hs:11:1) diff --git a/testsuite/tests/indexed-types/should_fail/T9554.stderr b/testsuite/tests/indexed-types/should_fail/T9554.stderr index 2bd5c2ab75..a8ae0bd885 100644 --- a/testsuite/tests/indexed-types/should_fail/T9554.stderr +++ b/testsuite/tests/indexed-types/should_fail/T9554.stderr @@ -21,4 +21,4 @@ T9554.hs:13:17: error: • In the first argument of ‘foo’, namely ‘Proxy’ In the expression: foo Proxy In the expression: - case foo Proxy of { Proxy -> putStrLn "Made it!" } + case foo Proxy of Proxy -> putStrLn "Made it!" diff --git a/testsuite/tests/polykinds/T14846.stderr b/testsuite/tests/polykinds/T14846.stderr index 83e32f7a21..e499241b77 100644 --- a/testsuite/tests/polykinds/T14846.stderr +++ b/testsuite/tests/polykinds/T14846.stderr @@ -31,9 +31,9 @@ T14846.hs:39:12: error: cls0 :: Struct cls -> Constraint cls1 :: k4 -> Constraint • In the expression: struct :: AStruct (Structured a cls) - In the expression: case struct :: AStruct (Structured a cls) of + In the expression: case struct :: AStruct (Structured a cls) of {} In an equation for ‘i’: - i = case struct :: AStruct (Structured a cls) of + i = case struct :: AStruct (Structured a cls) of {} • Relevant bindings include i :: Hom riki a a (bound at T14846.hs:39:3) diff --git a/testsuite/tests/polykinds/T9144.stderr b/testsuite/tests/polykinds/T9144.stderr index f58a57254b..b8de662f38 100644 --- a/testsuite/tests/polykinds/T9144.stderr +++ b/testsuite/tests/polykinds/T9144.stderr @@ -6,4 +6,4 @@ T9144.hs:34:26: error: • In the first argument of ‘toSing’, namely ‘n’ In the expression: toSing n In the expression: - case toSing n of { SomeSing n' -> SomeSing (SBar n') } + case toSing n of SomeSing n' -> SomeSing (SBar n') diff --git a/testsuite/tests/printer/T13199.stdout b/testsuite/tests/printer/T13199.stdout index 6ccc1f10f0..7184374835 100644 --- a/testsuite/tests/printer/T13199.stdout +++ b/testsuite/tests/printer/T13199.stdout @@ -19,9 +19,9 @@ T13199.hs:33:2-30: Splicing declarations T13199.hs:36:2-29: Splicing declarations [d| k = id @(Maybe Int) |] ======> k = id @(Maybe Int) T13199.hs:38:2-59: Splicing declarations - [d| l = case Just 'a' of { Just a -> Just ((\ x -> x) a) } |] + [d| l = case Just 'a' of Just a -> Just ((\ x -> x) a) |] ======> - l = case Just 'a' of { Just a -> Just ((\ x -> x) a) } + l = case Just 'a' of Just a -> Just ((\ x -> x) a) T13199.ppr.hs:11:2-42: Splicing declarations [d| instance C (Maybe a) (Maybe b) c |] ======> @@ -42,7 +42,7 @@ T13199.ppr.hs:16:2-29: Splicing declarations [d| j B {aa = a} = True |] ======> j B {aa = a} = True T13199.ppr.hs:17:2-29: Splicing declarations [d| k = id @(Maybe Int) |] ======> k = id @(Maybe Int) -T13199.ppr.hs:18:2-64: Splicing declarations - [d| l = case Just 'a' of { Just a -> Just ((\ x -> x) a) } |] +T13199.ppr.hs:18:2-60: Splicing declarations + [d| l = case Just 'a' of Just a -> Just ((\ x -> x) a) |] ======> - l = case Just 'a' of { Just a -> Just ((\ x -> x) a) } + l = case Just 'a' of Just a -> Just ((\ x -> x) a) diff --git a/testsuite/tests/th/T10603.stderr b/testsuite/tests/th/T10603.stderr index 3de6cb057b..2828bb078a 100644 --- a/testsuite/tests/th/T10603.stderr +++ b/testsuite/tests/th/T10603.stderr @@ -1,4 +1,4 @@ T10603.hs:5:17-69: Splicing expression - [| case Just 'a' of { Just a -> Just ((\ x -> x) a) } |] + [| case Just 'a' of Just a -> Just ((\ x -> x) a) |] ======> - case Just 'a' of { Just a -> Just ((\ x -> x) a) } + case Just 'a' of Just a -> Just ((\ x -> x) a) diff --git a/testsuite/tests/th/TH_StaticPointers02.stderr b/testsuite/tests/th/TH_StaticPointers02.stderr index a89ad11b0d..6d2c759ab8 100644 --- a/testsuite/tests/th/TH_StaticPointers02.stderr +++ b/testsuite/tests/th/TH_StaticPointers02.stderr @@ -2,11 +2,11 @@ TH_StaticPointers02.hs:11:34: error: • static forms cannot be used in splices: static 'a' • In the untyped splice: - $(case staticKey (static 'a') of { + $(case staticKey (static 'a') of Fingerprint w0 w1 -> let w0i = ... w1i = ... in [| fmap (\ p -> deRefStaticPtr p :: Char) $ unsafeLookupStaticPtr - $ Fingerprint (fromIntegral w0i) (fromIntegral w1i) |] }) + $ Fingerprint (fromIntegral w0i) (fromIntegral w1i) |]) diff --git a/testsuite/tests/th/TH_exn1.stderr b/testsuite/tests/th/TH_exn1.stderr index 69c854e244..2df704662c 100644 --- a/testsuite/tests/th/TH_exn1.stderr +++ b/testsuite/tests/th/TH_exn1.stderr @@ -3,4 +3,4 @@ TH_exn1.hs:1:1: error: Exception when trying to run compile-time code: TH_exn1.hs:(9,4)-(10,23): Non-exhaustive patterns in case - Code: (case reverse "no" of { [] -> return [] }) + Code: (case reverse "no" of [] -> return []) diff --git a/testsuite/tests/typecheck/should_compile/T12427a.stderr b/testsuite/tests/typecheck/should_compile/T12427a.stderr index efc87a1fc3..4516d4212c 100644 --- a/testsuite/tests/typecheck/should_compile/T12427a.stderr +++ b/testsuite/tests/typecheck/should_compile/T12427a.stderr @@ -7,7 +7,7 @@ T12427a.hs:17:29: error: at T12427a.hs:17:1-29 • In the expression: v In a case alternative: T1 _ v -> v - In the expression: case y of { T1 _ v -> v } + In the expression: case y of T1 _ v -> v • Relevant bindings include h11 :: T -> p (bound at T12427a.hs:17:1) diff --git a/testsuite/tests/typecheck/should_compile/T15370.stderr b/testsuite/tests/typecheck/should_compile/T15370.stderr index ec0ff67482..86cf969a9b 100644 --- a/testsuite/tests/typecheck/should_compile/T15370.stderr +++ b/testsuite/tests/typecheck/should_compile/T15370.stderr @@ -22,7 +22,7 @@ T15370.hs:20:13: warning: [-Wdeferred-type-errors (in -Wdefault)] Actual type: S r • In the expression: no + _ In a case alternative: Refl -> no + _ - In the expression: case mkRefl @x @y of { Refl -> no + _ } + In the expression: case mkRefl @x @y of Refl -> no + _ • Relevant bindings include no :: S r (bound at T15370.hs:18:7) right :: S r -> () (bound at T15370.hs:18:1) diff --git a/testsuite/tests/typecheck/should_compile/hole_constraints.stderr b/testsuite/tests/typecheck/should_compile/hole_constraints.stderr index c1796aad12..d4d92449f2 100644 --- a/testsuite/tests/typecheck/should_compile/hole_constraints.stderr +++ b/testsuite/tests/typecheck/should_compile/hole_constraints.stderr @@ -64,7 +64,7 @@ hole_constraints.hs:27:32: warning: [-Wtyped-holes (in -Wdefault)] • Found hole: _ :: String • In the expression: _ In a case alternative: AnyShow x -> _ - In the expression: case a of { AnyShow x -> _ } + In the expression: case a of AnyShow x -> _ • Relevant bindings include x :: a (bound at hole_constraints.hs:27:27) a :: AnyShow (bound at hole_constraints.hs:27:5) diff --git a/testsuite/tests/typecheck/should_compile/hole_constraints_nested.stderr b/testsuite/tests/typecheck/should_compile/hole_constraints_nested.stderr index 46c0c22a34..cf5344f659 100644 --- a/testsuite/tests/typecheck/should_compile/hole_constraints_nested.stderr +++ b/testsuite/tests/typecheck/should_compile/hole_constraints_nested.stderr @@ -3,7 +3,7 @@ hole_constraints_nested.hs:12:16: warning: [-Wtyped-holes (in -Wdefault)] • Found hole: _ :: Int • In the expression: _ In a case alternative: EqOrd -> _ - In the expression: case d2 of { EqOrd -> _ } + In the expression: case d2 of EqOrd -> _ • Relevant bindings include d2 :: EqOrd a (bound at hole_constraints_nested.hs:9:6) d1 :: a :~: b (bound at hole_constraints_nested.hs:9:3) diff --git a/testsuite/tests/typecheck/should_fail/tcfail069.stderr b/testsuite/tests/typecheck/should_fail/tcfail069.stderr index fcaf3e9542..75cfa11d5c 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail069.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail069.stderr @@ -4,4 +4,4 @@ tcfail069.hs:21:7: error: with actual type ‘[a0]’ • In the pattern: [] In a case alternative: [] -> error "foo" - In the expression: case (list1, list2) of { [] -> error "foo" } + In the expression: case (list1, list2) of [] -> error "foo" diff --git a/testsuite/tests/typecheck/should_fail/tcfail159.stderr b/testsuite/tests/typecheck/should_fail/tcfail159.stderr index 706b3afa32..5a49966637 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail159.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail159.stderr @@ -3,4 +3,4 @@ tcfail159.hs:9:11: error: • Expecting a lifted type, but got an unlifted type • In the pattern: ~(# p, q #) In a case alternative: ~(# p, q #) -> p - In the expression: case h x of { ~(# p, q #) -> p } + In the expression: case h x of ~(# p, q #) -> p diff --git a/testsuite/tests/typecheck/should_fail/tcfail180.stderr b/testsuite/tests/typecheck/should_fail/tcfail180.stderr index 7764b7798b..da7725fdb0 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail180.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail180.stderr @@ -3,4 +3,4 @@ tcfail180.hs:10:9: Couldn't match expected type ‘f0 b0’ with actual type ‘Bool’ In the pattern: True In a case alternative: True -> () - In the expression: case p of { True -> () } + In the expression: case p of True -> () diff --git a/testsuite/tests/typecheck/should_fail/tcfail201.stderr b/testsuite/tests/typecheck/should_fail/tcfail201.stderr index 77349e29f4..b1086f16f0 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail201.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail201.stderr @@ -11,7 +11,7 @@ tcfail201.hs:17:56: error: Actual type: c (HsDoc id0) • In the expression: z DocEmpty In a case alternative: DocEmpty -> z DocEmpty - In the expression: case hsDoc of { DocEmpty -> z DocEmpty } + In the expression: case hsDoc of DocEmpty -> z DocEmpty • Relevant bindings include hsDoc :: a (bound at tcfail201.hs:16:13) gfoldl' :: (forall a1 b. c (a1 -> b) -> a1 -> c b) diff --git a/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr b/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr index 532ca18ffc..8587eee34a 100644 --- a/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr +++ b/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr @@ -11,7 +11,7 @@ CaretDiagnostics1.hs:(5,3)-(7,16): error: = do 10000000000000000000000000000000000000 + 2 + (3 :: Int) pure ("this is not an IO" + ()) where - _ = case id of { "γηξ" -> () '0' } + _ = case id of "γηξ" -> () '0' | 5 | 10000000000000000000000000000000000000 + | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^... @@ -29,7 +29,7 @@ CaretDiagnostics1.hs:8:3-45: error: = do 10000000000000000000000000000000000000 + 2 + (3 :: Int) pure ("this is not an IO" + ()) where - _ = case id of { "γηξ" -> () '0' } + _ = case id of "γηξ" -> () '0' | 8 | pure ("this is not an IO" + ( )) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ @@ -48,7 +48,7 @@ CaretDiagnostics1.hs:13:7-11: error: • Couldn't match expected type ‘a1 -> a1’ with actual type ‘[Char]’ • In the pattern: "γηξ" In a case alternative: "γηξ" -> () '0' - In the expression: case id of { "γηξ" -> () '0' } + In the expression: case id of "γηξ" -> () '0' | 13 | "γηξ" -> ( | ^^^^^ |