Timo Meijer
Timo Meijer

Reputation: 119

Overlapping instances when modifying extensible record

I'm experimenting with extensible records (I'm using the row-types library) in my project, but I'm running into an issue when I want to modify something in the record in a specific way, which returns very scary errors about overlapping instances and non-deducible types.

What I'd like to express is a function that gets a record containing a specific label-type pair, and may modify that type. But when I try to use that function, the scary errors pop up.

I've reduced the error to the following example. Especially the error after enabling IncoherentInstances(Could not deduce: (Rec.Modify "x" [Double] r .! "x") ~ [Double]) seems weird to me, as it says right there that the record contains "x" :-> [Double]. I've tried avoiding the Rec.Modify with f2 :: forall r. (HasType aes a r) => Rec r -> Rec (r .- aes .+ aes .== b), but that results in a similar error.

I would love to get some help figuring out what I'm doing wrong, and how to make something like this work.

{-# LANGUAGE DataKinds, OverloadedLabels, TypeOperators, RankNTypes,
             RecordWildCards, NoMonomorphismRestriction #-}
module GoG.Temp where

import Data.Row
import qualified Data.Row.Records as Rec

type Scale' aes a = Scale aes a a
data Scale aes a b = Scale
  -- f1 works great
  -- f2 results in very scary errormessages
  { f1 :: forall r. (HasType aes a r) => Rec r -> Rec r
  -- What I'd like to express is a function that gets a record containing a
  -- specific label-type pair, and may modify that type. But when I try to
  -- use that function, the scary errors pop up
  , f2 :: forall r. (HasType aes a r) => Rec r -> Rec (Rec.Modify aes b r)
  -- ... other fields
  }

data Scales = Scales { _xScale :: Scale' "x" [Double] }

extractFromRecord :: (HasType "x" [Double] r, HasType "y" [Double] r) 
    => Rec r -> ()
extractFromRecord = undefined

render :: (HasType "x" [Double] r, HasType "y" [Double] r) 
    => Scales -> Rec r -> ()
-- If you replace f2 with f1 it works fine, but f2 results in the error
render Scales{..} r = extractFromRecord $ f2 _xScale r

This results in the following error:

    • Overlapping instances for HasType
                                  "x" [Double] (Rec.Modify "x" [Double] r)
        arising from a use of ‘extractFromRecord’
      Matching instances:
        instance forall k (r :: Row
                                  k) (l :: ghc-prim-0.5.3:GHC.Types.Symbol) (a :: k).
                 ((r .! l) ≈ a) =>
                 HasType l a r
          -- Defined in ‘Data.Row.Internal’
      There exists a (perhaps superclass) match:
        from the context: (HasType "x" [Double] r, HasType "y" [Double] r)
          bound by the type signature for:
                     render :: forall (r :: Row *).
                               (HasType "x" [Double] r, HasType "y" [Double] r) =>
                               Scales -> Rec r -> ()
          at /mnt/d/University/infoafp/afp-gog/src/GoG/Temp.hs:22:1-83
      (The choice depends on the instantiation of ‘r’
       To pick the first instance above, use IncoherentInstances
       when compiling the other instance declarations)
    • In the expression: extractFromRecord $ f2 _xScale r
      In an equation for ‘render’:
          render Scales {..} r = extractFromRecord $ f2 _xScale r
   |
23 | render Scales{..} r = extractFromRecord $ f2 _xScale r
   |                       ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

Or this if we enable IncoherentInstances as suggested:

    • Could not deduce: (Rec.Modify "x" [Double] r .! "x") ~ [Double]
        arising from a use of ‘extractFromRecord’
      from the context: (HasType "x" [Double] r, HasType "y" [Double] r)
        bound by the type signature for:
                   render :: forall (r :: Row *).
                             (HasType "x" [Double] r, HasType "y" [Double] r) =>
                             Scales -> Rec r -> ()
        at /mnt/d/University/infoafp/afp-gog/src/GoG/Temp.hs:23:1-83
    • In the expression: extractFromRecord $ f2 _xScale r
      In an equation for ‘render’:
          render Scales {..} r = extractFromRecord $ f2 _xScale r
    • Relevant bindings include
        r :: Rec r
          (bound at /mnt/d/University/infoafp/afp-gog/src/GoG/Temp.hs:24:19)
        render :: Scales -> Rec r -> ()
          (bound at /mnt/d/University/infoafp/afp-gog/src/GoG/Temp.hs:24:1)
   |
24 | render Scales{..} r = extractFromRecord $ f2 _xScale r
   |         

Upvotes: 3

Views: 148

Answers (1)

K. A. Buhr
K. A. Buhr

Reputation: 51029

The scary message is mostly irrelevant. This simplified example replaces HasType with its (.!) equivalent and illustrates the problem, which I think you've already discovered up above:

{-# LANGUAGE DataKinds, FlexibleContexts, TypeOperators, GADTs #-}

module MyRow where

import Data.Row
import qualified Data.Row.Records as Rec

f2 :: ((r .! "x") ~ Double) => Rec r -> Rec (Rec.Modify "x" Double r)
f2 = undefined

extract :: ((r .! "x") ~ Double) => Rec r -> ()
extract = undefined

render :: ((r .! "x") ~ Double) => Rec r -> ()
render r = extract $ f2 r

This code results in the error that (Modify "x" Double r .! "x") ~ Double cannot be deduced from (r .! "x") ~ Double. This may be "obviously" true, but that doesn't mean GHC can prove it.

I'd be happy to be proven wrong, but I think you'll be forced to add the explicit constraints you need. In your original example, the following type signature (which GHC is able to deduce on its own if you leave it out), appears to work:

render ::
  ( HasType "x" [Double] r
  , HasType "x" [Double] (Rec.Modify "x" [Double] r)
  , HasType "y" [Double] (Rec.Modify "x" [Double] r)
  ) => Scales -> Rec r -> ()
render Scales{..} r = extractFromRecord $ f2 _xScale r

I had to turn FlexibleContexts and GADTs on, in addition to the other extensions you had enabled in your example.

Upvotes: 2

Related Questions