Missing strict fields [GHC-95909]

When strict fields are declared for a datatype – either per-field with a strictness flag !, or for an entire type using the language extensions Strict/StrictData – all strict fields are strictly evaluated by constructors. Therefore, it is not possible to leave some strict fields unassigned, because they can’t be given a suspended bottom as a placeholder.

Therefore, it is required that all strict fields for a constructor are assigned on construction of the type.

If a non-strict field is missing, the warning GHC-20125 is emitted instead.

Examples

Missing strict field in record syntax

The instantiation of a strict field in a record is missing. In aFine, we can leave one field uninstantiated as it is not strict, and therefore is not evaluated until needed, due to lazy evaluation. However in aBad we cannot, as the field a is strict.

Error Message

MissingStrictField.hs:12:8: error: [GHC-95909]
    • Constructor ‘A’ does not have the required strict field(s): a
    • In the expression: A {b = 5}
      In an equation for ‘aBad’: aBad = A {b = 5}
   |
12 | aBad = A { b = 5 }
   |        ^^^^^^^^^^^
MissingStrictField.hs
Before
module MissingStrictField where

data A = A
    { a :: !Bool
    , b :: Int
    }

aFine :: A
aFine = A { a = True }

aBad :: A
aBad = A { b = 5 }
After
module MissingStrictField where

data A = A
    { a :: !Bool
    , b :: Int
    }

aFine :: A
aFine = A { a = True }

aFixed :: A
aFixed = A { a = True, b = 5 }
All fields are strict if the StrictData language extension is enabled

When using the language extension {-# LANGUAGE Strict #-} or {-# LANGUAGE StrictData #-}, all fields are strict, even if we do not explicitly use the strictness flag !. Thus, we must instantiate all fields on construction.

Error Message

StrictExtension.hs:9:8: error:  [GHC-95909]
    • Constructor ‘A’ does not have the required strict field(s): b
    • In the expression: A {a = True}
      In an equation for ‘aBad’: aBad = A {a = True}
  |
9 | aBad = A { a = True }
  |        ^^^^^^^^^^^^^^

StrictExtension.hs:12:12: error: [GHC-95909]
    • Constructor ‘A’ does not have the required strict field(s): a
    • In the expression: A {b = 5}
      In an equation for ‘aAlsoBad’: aAlsoBad = A {b = 5}
   |
12 | aAlsoBad = A { b = 5 }
   |            ^^^^^^^^^^^
StrictExtension.hs
Before
{-# LANGUAGE Strict #-}

module StrictExtension where

data A = A
    { a :: Bool
    , b :: Int
    }

aBad :: A
aBad = A { a = True }

aAlsoBad :: A
aAlsoBad = A { b = 5 }
After
{-# LANGUAGE Strict #-}

module StrictExtension where

data A = A
    { a :: Bool
    , b :: Int
    }

aFixed :: A
aFixed = A { a = True, b = 5 }

aAlsoFixed :: A
aAlsoFixed = A { a = True, b = 5 }