基于另一个 class 派生一个类型的 class 实例,它是

Deriving a class instance for a type based on another class it's an instance of

我有一些类似的 newtypes,它们都需要是 RandomArbitrary 和许多其他东西的实例。他们都需要相同函数randomRrandomarbitrary等自定义实现。所以我将所有这些实现放在class.

这是一个简化的例子,它只处理 Random.

{-# LANGUAGE ConstrainedClassMethods #-}
{-# LANGUAGE FlexibleContexts        #-}
{-# LANGUAGE ScopedTypeVariables     #-}
{-# LANGUAGE StandaloneDeriving      #-}
{-# LANGUAGE TypeFamilies            #-}

import qualified System.Random as SR

-- Numbers that are restricted to a narrower range
class Narrow t where
  type BaseType t

  -- Unsafe constructor for the instance type
  bless :: BaseType t -> t

  -- Safe constructor for the instance type
  narrow :: (Ord t, Bounded t) => BaseType t -> t
  narrow x | x' < (minBound :: t) = error "too small"
           | x' > (maxBound :: t) = error "too big"
           | otherwise     = x'
    where x' = bless x :: t

  -- Deconstructor for the instance type
  wide :: t -> BaseType t

  -- Random
  randomR
    :: (Ord t, Bounded t, SR.Random (BaseType t), SR.RandomGen g)
    => (t, t) -> g -> (t, g)
  randomR (a, b) g = (narrow x, g')
    where (x, g') = SR.randomR (wide a, wide b) g

  random
    :: (Ord t, Bounded t, SR.Random t, SR.RandomGen g)
    => g -> (t, g)
  random = SR.randomR (minBound, maxBound)

这是我想要的类型之一的示例。

-- | A number on the unit interval
newtype UIDouble = UIDouble Double
  deriving (Eq, Ord)

instance Bounded UIDouble where
  minBound = UIDouble 0
  maxBound = UIDouble 1

instance Narrow UIDouble where
  type BaseType UIDouble = Double
  bless = UIDouble
  wide (UIDouble x) = x
    

我希望这是 Random 的一个实例。理想情况下,我想写这样的东西:

deriving ?strategy? instance SR.Random UIDouble

并让编译器知道使用 Narrow 中定义的方法来实现 Random。但是我必须写

instance SR.Random UIDouble where
  randomR = randomR
  random = random

对某些方法执行此操作没有问题,但对 NumFractionalRealFracFloatingSerialize 执行此操作没有问题等等对于我的每个类型来说都有点乏味。

我探索过的另一种方法是编写

instance (Narrow t) => SR.Random t where
  randomR = randomR
  random = random

因为我只需要为 class 写一次,而不是为每种类型重复它。但这会导致 UndecidableInstances 我知道这是不好的。我可以用 TemplateHaskell 做到这一点,我敢肯定。 但我想知道是否有一些奇特的语言编译指示或类型级编程魔法可以简化这个过程?

首先你定义一个新类型并一劳永逸地给它一个你想要的实例:

newtype UseNarrow a = UN a
instance Narrow a => SR.Random (UseNarrow a) where
    randomR (UN lo, UN hi) g = (UN v, g) where v = randomR (lo, hi) g
    random g = (UN v, g) where v = random g

然后在所有你想使用那个实例的地方,你写:

deriving via (UseNarrow UIDouble) instance SR.Random UIDouble

我可能有一些语法错误,因为我没有测试上面的内容。但是你应该有想法。

如需进一步阅读,请在 GHC 用户手册中查找 DerivingVia