修改可扩展记录时的重叠实例



我正在我的项目中试验可扩展记录(我正在使用行类型库(,但是当我想以特定方式修改记录中的某些内容时,我遇到了一个问题,这返回了关于重叠实例和不可推导类型的非常可怕的错误。

我想表达的是一个函数,它获取包含特定标签类型对的记录,并可能修改该类型。但是当我尝试使用该功能时,会弹出可怕的错误。

我已将错误减少到以下示例。尤其是启用IncoherentInstances(Could not deduce: (Rec.Modify "x" [Double] r .! "x") ~ [Double](后的错误对我来说似乎很奇怪,因为它在那里说记录包含"x" :-> [Double]。我尝试避免使用f2 :: forall r. (HasType aes a r) => Rec r -> Rec (r .- aes .+ aes .== b) Rec.Modify,但这会导致类似的错误。

我很想得到一些帮助,弄清楚我做错了什么,以及如何让这样的事情发挥作用。

{-# 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

这会导致以下错误:

    • 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
   |                       ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

或者,如果我们按照建议启用 IncoherentInstances:

    • 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
   |         

可怕的信息大多无关紧要。 这个简化的示例将HasType替换为其(.!)等效物,并说明了问题,我想您在上面已经发现了这个问题:

{-# 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

此代码会导致无法从(r .! "x") ~ Double推断出(Modify "x" Double r .! "x") ~ Double的错误。 这可能"显然"是正确的,但这并不意味着GHC可以证明这一点。

我很高兴被证明是错的,但我认为你会被迫添加你需要的显式约束。 在您的原始示例中,以下类型签名(如果您省略它,GHC 能够自行推断(似乎有效:

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

除了您在示例中启用的其他扩展之外,我还必须打开FlexibleContexts并打开GADTs

最新更新