Lambda syntax in pattern [GHC-00482]

When pattern matching, lambda expressions are not allowed as patterns to be matched against.

Examples

Lambda syntax in `case` expression

When pattern matching with a case expression, backslash (\) is not required before the pattern.

Error Message

LambdaInCase.hs:6:5: error: [GHC-00482]
    Lambda-syntax in pattern.
    Pattern matching on functions is not possible.
  |
6 |     \a -> a
  |     ^^^^^^^
LambdaInCase.hs
Before
module LambdaInCase where

f :: Int -> Int
f x =
  case x of
    \a -> a
After
module LambdaInCase where

f :: Int -> Int
f x =
  case x of
    a -> a
Lambda syntax in pattern match

Pattern matching on functions is not possible.

Error Message

LambdaInPattern.hs:4:4: error: [GHC-00482]
    Lambda-syntax in pattern.
    Pattern matching on functions is not possible.
  |
4 | f (\a -> a) = 0
  |    ^^^^^^^
LambdaInPattern.hs
Before
module LambdaInPattern where

f :: (Int -> Int) -> Int
f (\a -> a) = 0
After
module LambdaInPattern where

f :: (Int -> Int) -> Int
f a = a 0