Illegal unboxed string literal in pattern [GHC-69925]

When pattern matching, unboxed string literals (with the MagicHash postfix) are not allowed. Unboxed string literals are essentially C strings allocated outside of the Haskell heap, and they evaluate to pointers to the resulting strings. Thus,"foo"# is of type Addr#. While eqAddr# can be used to compare these pointers, two identically-written unboxed string literals typically do not point to the same address.

Examples

Illegal unboxed string literal in pattern

When pattern matching, unboxed string literals (with the MagicHash postfix) are not allowed.

Error Message

IllegalUnboxedString.hs:6:5: error: [GHC-69925]
    Illegal unboxed string literal in pattern:
    "a"#
  |
6 |     "a"# -> True
  |     ^^^^
IllegalUnboxedString.hs
Before
{-# LANGUAGE MagicHash #-}

module IllegalUnboxedString where

import GHC.Prim

g :: Addr# -> Bool
g y = case y of
    "a"# -> True
    _    -> False
After
module IllegalUnboxedString where

g :: String -> Bool
g y = case y of
    "a" -> True
    _ -> False