Case expression included in pattern [GHC-53786]

A pattern (e.g. in a function definition or a pattern match) may not contain case ... of ... syntax. See here for an overview of the syntax and semantics of patterns and pattern matching in Haskell.

Examples

Case expression in case pattern

The pattern being matched upon in the case expression case x of ... contains another case expression.

Error Message

CaseExprInCasePattern.hs:5:3: error: [GHC-53786]
    (case ... of ...)-syntax in pattern
  |
5 |   case y of
  |   ^^^^^^^^^...
CaseExprInCasePattern.hs
Before
module CaseExprInFunctionDef where

f :: a -> b -> Int
f x y = case x of
  case y of
    _ -> 1
After
module CaseExprInFunctionDef where

f :: a -> b -> Int
f x y = case x of
  _ -> case y of
    _ -> 1
Case expression in do-block

The expression in one branch of the case expression is a do-block that’s missing a do. This triggers a corner case in the grammar of Haskell, and the case-expression is interpreted as the pattern part of a bind statement in the top-level do-block.

More details are available on the GHC issue tracker, issue #984.

Error Message

CaseExprInDoBlock.hs:5:3: error: [GHC-53786]
    (case ... of ...)-syntax in pattern
  |
5 |   case () of
  |   ^^^^^^^^^^...
CaseExprInDoBlock.hs
Before
module CaseExprInDoBlock where

x :: [a]
x = do
  case () of
    () ->
      a <- []
      pure a
After
module CaseExprInDoBlock where

x :: [a]
x = do
  case () of
    () -> do
      a <- []
      pure a
Case expression in function argument pattern

The pattern on the left-hand side of the function definition contains a case ... of ... expression.

Error Message

CaseExprInFunctionDef.hs:3:4: error: [GHC-53786]
    (case ... of ...)-syntax in pattern
  |
3 | f (case x of { Nothing -> 0; Just a -> a }) = a
  |    ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
CaseExprInFunctionDef.hs
Before
module CaseExprInFunctionDef where

f (case x of { Nothing -> 0; Just a -> a }) = a
After
module CaseExprInFunctionDef where

f Nothing = 0
f (Just a) = a