[Haskell-cafe] Cannot update a field in a record with a polymorphic type.

Viktor Dukhovni ietf-dane at dukhovni.org
Thu Sep 10 11:28:09 UTC 2020


On Thu, Sep 10, 2020 at 11:03:59AM +0100, Tom Ellis wrote:

> Ah, I see.  You are saying that record updates can have a special
> typing rule because we have extra information that tells us that the
> type of the result cannot depend on the type of what was previously
> there.

Here's an example where the previous value matters:

    λ> data Y a = Y { y :: !a } deriving Show
    λ> defaultY :: Monoid a => Y a ; defaultY = Y undefined
    λ> monoUpdate :: Y a -> a -> Y a; monoUpdate r a = r { y = a }
    λ> monoUpdate defaultY "c"
    *** Exception: Prelude.undefined
    CallStack (from HasCallStack):
      error, called at libraries/base/GHC/Err.hs:79:14 in base:GHC.Err
        undefined, called at <interactive>:2:44 in interactive:Ghci2

[ The construction of "defaultY { y = "c" }" begins with a construction of
  "defaultY" that may fail. ]

Now imagine that some Monoid instances have "mempty = undefined", and
others do not.  Making the constructor strict,

When the struct record is strict in the updated field, (e.g. with
StrictData), the initial value is constructed strictly, even with
optimisation.  For example the below compiled with "ghc -O2" still
throws an exception when executed:

    {-# LANGUAGE StrictData #-}
    module Main (main) where

    data Y a = Y { y :: a } deriving Show
    defaultY :: Monoid a => Y a;    defaultY = Y undefined
    monoUpdate :: Y a -> a -> Y a;  monoUpdate r a = r { y = a }

    main :: IO ()
    main = print $ monoUpdate defaultY "c"

Turning off "StrictData" makes it go.  So I think there's even less room
here for special logic.  The type ambiguity must be resolved, allowing
defaultY to be constructed.

-- 
    Viktor.


More information about the Haskell-Cafe mailing list