可以通过中间步骤来消除实例的歧义吗?

huangapple go评论103阅读模式
英文:

Is it possible to disambiguate instances with an intermediate step?

问题

假设一种情况,你有一个应用程序配置,其结构已经多次更改。为了使用户更容易使用,你希望允许从每个版本自动迁移到下一个版本。

以下代码展示了这样的场景,将配置表示为VersionedConfig,其参数化为配置结构的版本。

鉴于可以在任意两个连续版本之间进行迁移(V1 -> V2V2 -> V3等),是否可以编写MigrateableFromTo的实例,该实例以正确的顺序组合这些实例以形成完整的更改集?

-- 代码不做翻译
英文:

Suppose a scenario where you have an application config, the structure of which has changed a few times. To provide ease of use for users, you wish to allow automatic migration from each version to the next.

The code below shows such a scenario, representing the configuration as VersionedConfig, which is parameterised over the version of the configuration structure.

Given it is possible to migrate between any two successive versions (V1 -> V2, V2 -> V3 and so on), is it possible to write an instance of MigrateableFromTo which composes those instances in the correct order to form the complete set of changes?

{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UndecidableInstances #-}

-- | Represents different versions of a config file
data ConfigVersion = V1 | V2 | V3

-- | Represents the config itself, at different versions
data VersionedConfig (v :: ConfigVersion) where
  CV1 :: Int -> VersionedConfig V1
  CV2 :: Integer -> VersionedConfig V2
  CV3 :: String -> VersionedConfig V3
  
deriving instance Show (VersionedConfig v)
  
-- | Proof term for migration between versions
data MigrateableProof (from :: ConfigVersion) (to :: ConfigVersion) where
  MigrateableProof :: (VersionedConfig from -> VersionedConfig to) -> MigrateableProof from to
  
class MigrateableFromTo (from :: ConfigVersion) (to :: ConfigVersion) where
  migrateFromTo :: MigrateableProof from to
  
instance MigrateableFromTo V1 V2 where
  migrateFromTo = MigrateableProof (\(CV1 a) -> CV2 (toEnum a))
  
instance MigrateableFromTo V2 V3 where
  migrateFromTo = MigrateableProof (\(CV2 a) -> CV3 (show a))
  
instance forall from intermediate to.
  (MigrateableFromTo from intermediate, MigrateableFromTo intermediate to)
  => MigrateableFromTo from to where
  migrateFromTo = MigrateableProof (applyMigration @intermediate . applyMigration)
    
applyMigration :: MigrateableFromTo from to => VersionedConfig from -> VersionedConfig to
applyMigration = let MigrateableProof f = migrateFromTo in f 

main :: IO ()
main = do
  let
    cv1 = CV1 5
    cv3 = (applyMigration cv1) :: VersionedConfig V3
  print cv3

This code won't compile as from,intermediate, and to in the inductive instance could be the same type. Is it possible to disambiguate this such that the code compiles?

The result at present is as follows:


Main.hs:44:12: error:
     Overlapping instances for MigrateableFromTo intermediate0 'V3
        arising from a use of applyMigration
      Matching instances:
        instance (MigrateableFromTo from intermediate,
                  MigrateableFromTo intermediate to) =>
                 MigrateableFromTo from to
          -- Defined at Main.hs:32:10
        instance MigrateableFromTo 'V2 'V3 -- Defined at Main.hs:29:10
      (The choice depends on the instantiation of intermediate0
       To pick the first instance above, use IncoherentInstances
       when compiling the other instance declarations)
     In the expression: (applyMigration cv1) :: VersionedConfig V3
      In an equation for cv3:
          cv3 = (applyMigration cv1) :: VersionedConfig V3
      In the expression:
        do let cv1 = CV1 5
               cv3 = ...
           print cv3
   |
44 |     cv3 = (applyMigration cv1) :: VersionedConfig V3
   |            ^^^^^^^^^^^^^^

This code is available in the Haskell Playground.

答案1

得分: 5

是的,这是可能的。深呼吸:

{-# Language AllowAmbiguousTypes #-}
{-# Language DataKinds #-}
{-# Language FlexibleContexts #-}
{-# Language FlexibleInstances #-}
{-# Language MultiParamTypeClasses #-}
{-# Language ScopedTypeVariables #-}
{-# Language TypeApplications #-}
{-# Language TypeFamilies #-}
{-# Language TypeOperators #-}
{-# Language UndecidableInstances #-}

import Data.Kind

这是你需要为其编写实例的单步类:

class DirectlyConvertible a where
    type DirectConversion a
    convertDirectly :: a -> DirectConversion a

这是支持的机制,只需要完成一次:

class ConvertibleVia (path :: [*]) tgt where
    type From path tgt
    convert_ :: From path tgt -> tgt

instance ConvertibleVia '[] a where
    type From '[] a = a
    convert_ = id

instance (DirectlyConvertible a, DirectConversion a ~ From path c, ConvertibleVia path c) => ConvertibleVia (a:path) c where
    type From (a:path) c = a
    convert_ = convert_ @path . convertDirectly

type family ConversionPath a b where
    ConversionPath a a = '[]
    ConversionPath a b = a : ConversionPath (DirectConversion a) b

-- 一个小包装器,使类型应用变得更方便
convert :: forall src tgt path. (path ~ ConversionPath src tgt, ConvertibleVia path tgt, From path tgt ~ src) => src -> tgt
convert = convert_ @path

有了这个,我们可以添加一些模拟实例:

data V1
data V2
data V3
data V4
instance DirectlyConvertible V1 where type DirectConversion V1 = V2
instance DirectlyConvertible V2 where type DirectConversion V2 = V3
instance DirectlyConvertible V3 where type DirectConversion V3 = V4

现在你可以写 convert @V1 @V4,甚至是 convert @V1 如果 V4 可以从上下文中推断出,它会正常工作。有趣的是,通过打开 AllowAmbiguousTypes 来消除实例解析的歧义,不是吗?

英文:

Yes, it's possible. Deep breath:

{-# Language AllowAmbiguousTypes #-}
{-# Language DataKinds #-}
{-# Language FlexibleContexts #-}
{-# Language FlexibleInstances #-}
{-# Language MultiParamTypeClasses #-}
{-# Language ScopedTypeVariables #-}
{-# Language TypeApplications #-}
{-# Language TypeFamilies #-}
{-# Language TypeOperators #-}
{-# Language UndecidableInstances #-}
import Data.Kind

Here's the one-step class that you need to write instances for:

class DirectlyConvertible a where
type DirectConversion a
convertDirectly :: a -> DirectConversion a

And here's the supporting machinery that need only be done once:

class ConvertibleVia (path :: [*]) tgt where
type From path tgt
convert_ :: From path tgt -> tgt
instance ConvertibleVia '[] a where
type From '[] a = a
convert_ = id
instance (DirectlyConvertible a, DirectConversion a ~ From path c, ConvertibleVia path c) => ConvertibleVia (a:path) c where
type From (a:path) c = a
convert_ = convert_ @path . convertDirectly
type family ConversionPath a b where
ConversionPath a a = '[]
ConversionPath a b = a : ConversionPath (DirectConversion a) b
-- tiny wrapper to make the type applications a bit more convenient
convert :: forall src tgt path. (path ~ ConversionPath src tgt, ConvertibleVia path tgt, From path tgt ~ src) => src -> tgt
convert = convert_ @path

With that in place, we can toss in some mock instances:

data V1
data V2
data V3
data V4
instance DirectlyConvertible V1 where type DirectConversion V1 = V2
instance DirectlyConvertible V2 where type DirectConversion V2 = V3
instance DirectlyConvertible V3 where type DirectConversion V3 = V4

And now you can write e.g. convert @V1 @V4, or even convert @V1 if the V4 can be inferred from context, and it will Just Work. Ironic that disambiguating the instance resolution is done by turning on AllowAmbiguousTypes, isn't it?

答案2

得分: 1

以下是翻译好的部分:

这是我发现特别容易阅读的一种方法。

这种方法不需要类型类。我只在最后给出一个类型类,以便更容易使用。而且,这个类型类恰好做了一些非常熟悉的事情。

这种方法基于这样的观察,迁移完全由连续版本之间发生的事情定义(1 -> 2,2 -> 3等等)。我们如何谈论“版本的后继”呢?

另一个关键点是,我们想要定义一个函数,该函数将接受版本a至少与版本b一样旧的证明,并返回一个MigrateableProof a b

我首先像这样通用化版本类型,这将使我们能够谈论“后继版本”:

data Natural = Z | S Natural
  deriving (Show)

-- | 代表配置文件的不同版本
type ConfigVersion = Natural

type V1 = Z
type V2 = S V1
type V3 = S V2

这种方法有利有弊。主要好处是你可以轻松地谈论后继版本。现在你也可以谈论任何未来版本。如果你只想谈论已经存在的版本,这可能被视为不足。不过,我不认为这太大的问题。我们将在下面讨论这个问题。

我们像这样重新实现VersionedConfig

-- | 代表配置本身,不同版本
data VersionedConfig (v :: ConfigVersion) where
  CV1 :: Int -> VersionedConfig V1
  CV2 :: Integer -> VersionedConfig V2
  CV3 :: String -> VersionedConfig V3

这只使用实际存在的版本。这就是为什么我认为现在可以在ConfigVersion类型中表示不存在的版本不是太大的问题。

现在,我们可以实现一个函数,(只)将版本迁移到其后继版本:

migrateToSuccessor :: MigrateableProof from (S from)
migrateToSuccessor = MigrateableProof $ \case
  CV1 a ->    -- 1 -> 2
    CV2 (toEnum a)

  CV2 a ->    -- 2 -> 3
    CV3 (show a)

在我们通用化之前,我们需要一种方式来表达版本小于或等于另一个版本的证明:

data (:<=) :: Natural -> Natural -> Type where
  Refl :: a :<= a
  LtS :: a :<= b -> a :<= S b

deriving instance Show (a :<= b)

有了这个,我们可以得到通用的迁移函数:

migrate :: from :<= to -> MigrateableProof from to
migrate Refl = id
migrate (LtS prf) = migrateToSuccessor . migrate prf

请注意,我为MigrateableProof使用了Category实例,以使其更可读。

到目前为止,我们不需要任何类型类,但构造:<=证明有些繁琐。为了简化这一点,我们可以创建一个类型类,该类型类将自动生成适当的:<=值(证明):

class Le a b where
  le :: a :<= b

instance Le Z Z where
  le = Refl

instance forall a b. Le a b => Le (S a) (S b) where
  le =
    case le @a @b of
      Refl -> Refl
      LtS prf -> LtS (leStepBoth prf)

leStepBoth :: a :<= b -> S a :<= S b
leStepBoth Refl = Refl
leStepBoth (LtS prf) = LtS $ leStepBoth prf

最后,我们可以定义applyMigration并像这样重写main

applyMigration :: from :<= to -> VersionedConfig from -> VersionedConfig to
applyMigration prf = let MigrateableProof f = migrate prf in f

main :: IO ()
main =
  let
    cv1 = CV1 5
    cv3 = applyMigration le cv1 :: VersionedConfig V3
  in
  print cv3

优点和缺点

这个方法的一个缺点是,我们使用了“:<=”证明的运行时表示,这可能比在编译时完全解析要低效一些。不过,我认为在实际应用中,这不太可能成为性能瓶颈。

此外,无论如何,我们都需要构造一个MigrateableProof值。可以这样理解:migratea :&lt;= b的证明转换为从版本a到版本b的“可迁移证明”。

另一方面,这个方法的一个好处是我们最小化了多态递归类型类和类型类技巧的使用。这种类型类通常会有些复杂。我认为将事情分开像这样使代码更清晰,更有组织性。

一个局限是这种方法只能表示由“后继迁移”独占给出的迁移。

我认为可以修改这种方法以允许其他类型的迁移(例如,如果有一种更好的方法迁移1 -&gt; 6而不必经过每个后继迁移)。如果要进行这种改进,这方面的关键初步观察可能是:

  1. “:<=”的“结构”是“薄的”。换句话说:对于任何版本ab
英文:

Here is one approach that I find particularly easy to read.

No type classes are necessary for this approach. I only give a type class at the very end to make it easier to work with. Not only that, but that type class happens to do something very familiar.

This approach is based on the observation that migration is defined entirely by what happens between successive versions (1 -> 2, 2 -> 3, etc). How might we talk about "version successors?"

The other key point is that we want to define a function that will take a proof that version a is at least as old as version b and give back a MigrateableProof a b.

I would first generalize the version type like this, which will let us talk about "successor versions":

data Natural = Z | S Natural
deriving (Show)
-- | Represents different versions of a config file
type ConfigVersion = Natural
type V1 = Z
type V2 = S V1
type V3 = S V2

There are upsides and downsides to this. The main upside is that you can easily talk about successor versions. You can also now talk about any future versions. That might be seen as a downside if you only want to talk about versions that already exist. I don't think this is too much of a downside though. We will get to that next.

We re-implement VersionedConfig like this:

-- | Represents the config itself, at different versions
data VersionedConfig (v :: ConfigVersion) where
CV1 :: Int -&gt; VersionedConfig V1
CV2 :: Integer -&gt; VersionedConfig V2
CV3 :: String -&gt; VersionedConfig V3

This only uses the versions that actually exist. This is why I don't think it's much of a downside that we now can represent non-existent versions in the ConfigVersion type.

Now, we can implement a function which (only) migrates a version to its successor:

migrateToSuccessor :: MigrateableProof from (S from)
migrateToSuccessor = MigrateableProof $ \case
CV1 a -&gt;    -- 1 -&gt; 2
CV2 (toEnum a)
CV2 a -&gt;    -- 2 -&gt; 3
CV3 (show a)

Before we generalize, we need a way to express proofs that a version is less than or equal to another version:

data (:&lt;=) :: Natural -&gt; Natural -&gt; Type where
Refl :: a :&lt;= a
LtS :: a :&lt;= b -&gt; a :&lt;= S b
deriving instance Show (a :&lt;= b)

From this, we can get the general migration function:

migrate :: from :&lt;= to -&gt; MigrateableProof from to
migrate Refl = id
migrate (LtS prf) = migrateToSuccessor . migrate prf

Note that I've used a Category instance for MigrateableProof to make that more readable.<sup>[1]</sup> The instance is defined like this:

instance Category MigrateableProof where
id = MigrateableProof id
MigrateableProof p . MigrateableProof q = MigrateableProof (p . q)

So far, we haven't needed any type classes but constructing :&lt;= proofs is tedious. In order to simplify this, we can make a type class that will automatically generate :&lt;= values (proofs) where appropriate:

class Le a b where
le :: a :&lt;= b
instance Le Z Z where
le = Refl
instance forall a b. Le a b =&gt; Le (S a) (S b) where
le =
case le @a @b of
Refl -&gt; Refl
LtS prf -&gt; LtS (leStepBoth prf)
leStepBoth :: a :&lt;= b -&gt; S a :&lt;= S b
leStepBoth Refl = Refl
leStepBoth (LtS prf) = LtS $ leStepBoth prf

Finally, we can define applyMigration and rewrite main like this:

applyMigration :: from :&lt;= to -&gt; VersionedConfig from -&gt; VersionedConfig to
applyMigration prf = let MigrateableProof f = migrate prf in f
main :: IO ()
main =
let
cv1 = CV1 5
cv3 = applyMigration le cv1 :: VersionedConfig V3
in
print cv3

Pros and cons

A drawback of this is that we are using a runtime representation of :&lt;= proofs which is probably a bit less efficient than if it was resolved entirely at compile-time. I think it's very unlikely that this will be a performance bottleneck in an actual application, though.

Besides, we need to construct a MigrateableProof value regardless. Think of it like this: migrate turns a proof of a :&lt;= b into a "migrateable proof" from version a to version b.

On the other hand, a benefit of this is that we minimize the usage of polymorphically recursive type classes and type class tricks in general. Such type classes can otherwise be somewhat complicated. I think separating things out like this makes the code more clear and better organized.

A limitation is that this approach can only express migrations that are exclusively given by "successor migrations."

I think it would be possible to modify the approach to allow for other migrations as well (for example, if there is a better way to migrate 1 -&gt; 6 than going through each successor migration).

If you want to make this improvement, the key initial observations for this are probably:

  1. The "structure" of :&lt;= is "thin." To put it another way: For any versions a and b, a :&lt;= b can only hold in at most one way.<sup>[2]</sup>
  2. The migrate function reflects the structure of the :&lt;= value into the resulting MigrationProof value.<sup>[3]</sup>

At least one of those would need to be addressed.<sup>[4]</sup>

There is another limitation and a fix: migrateToSuccessor allows you to attempt to create the successor of the most recent version. As a result, so does migrate. One way to fix this is to package the code up into a module, avoid exporting migrate and applyMigration and instead export these constrained functions:

type VersionInBound a = Le a V3
migrateSafe :: (VersionInBound to, Le from to) =&gt; MigrateableProof from to
migrateSafe = migrate le
applyMigration :: (VersionInBound to, Le from to) =&gt; VersionedConfig from -&gt; VersionedConfig to
applyMigration = let MigrateableProof f = migrate le in f 

<sup>[1]</sup> <sup>In order to use this Category instance like I have, you will need import Prelude hiding (id, (.)) to avoid name clashes as well as import Control.Category</sup>

<sup>[2]</sup> <sup> Here is a theoretical point that is not necessary to understand what I've described here, but for completeness: I'm using "thin" in this sense.</sup>

<sup>[3]</sup> <sup> There is another theoretical point that explains this bulletpoint, which is also not necessary to understand: The migrate function is actually a functor from the :&lt;= preorder category to the MigrateableProof category. This is the categorical reason that migrate "reflects the structure of :&lt;= into MigrateableProof." To be more explicit, we run into issues because of the composition law for functors: migrate (f . g) = migrate f . migrate g. This is exactly what we don't want if there are multiple ways to migrate between versions and we want migrate to choose the way that's better than using successors when possible </sup>

<sup>[4]</sup> <sup> To again state this in categorical terms using the previous two footnotes, we want to do at least one of the following two things: (1) Replace :&lt;= with a category that is not thin. (2) Re-implement migrate knowing that it should not be a functor. </sup>

huangapple
  • 本文由 发表于 2023年3月7日 01:38:44
  • 转载请务必保留本文链接:https://go.coder-hub.com/75654068.html
匿名

发表评论

匿名网友

:?: :razz: :sad: :evil: :!: :smile: :oops: :grin: :eek: :shock: :???: :cool: :lol: :mad: :twisted: :roll: :wink: :idea: :arrow: :neutral: :cry: :mrgreen:

确定