Illegal datatype context [GHC-87429]
Without the language extension DatatypeContexts
enabled, it is illegal to add constraints to the context of a datatype definition. Whilst this can be solved with enabling DatatypeContexts
, however this extension is deprecated and is considered a misfeature. Other solutions to fix this can include:
- Placing constraints on the use-site of a datatype, or
- Using GADTs to place constraints on specific datatype constructors.
Examples
Illegal datatype context, fixed with use-site constraints
In this example, we wish to constrain the type a
which can parameterise the type D
to a type that implements the Show
and Read
typeclasses. Whilst this can be solved currently by -XDatatypeContexts
, this extension is deprecated.
Instead, a solution is to put the constraints on functions that use the datatype.
Error Message
IllegalDatatypeContext.hs:5:6: error: [GHC-87429]
Illegal datatype context (use DatatypeContexts): (Show a) =>
|
5 | data (Show a) => D a = D a
| ^^^^^^^
IllegalDatatypeContext.hs
module IllegalDatatypeContext where
data (Show a) => D a = D a
module IllegalDatatypeContext where
data D a = D a
f :: (Show a) => D a -> IO ()
f (D d) = putStrLn (show d)
Illegal datatype context, fixed with GADTs
In this example, we wish to constrain the type a
which can parameterise the type D
to a type that implements the Show
and Read
typeclasses. Whilst this can be solved currently by -XDatatypeContexts
, this extension is deprecated.
Instead, a solution is to use a GADT to provide a constructor with the given constraints.
Error Message
IllegalDatatypeContext.hs:5:6: error: [GHC-87429]
Illegal datatype context (use DatatypeContexts): (Show a,
Read a) =>
|
5 | data (Show a, Read a) => D a = D a
| ^^^^^^^^^^^^^^^^
IllegalDatatypeContext.hs
module IllegalDatatypeContext where
data (Show a, Read a) => D a = D a
{-# LANGUAGE GADTs #-}
module IllegalDatatypeContext where
data D a where
ShowReadD :: (Show a, Read a) => a -> D a