首页 > 解决方案 > 是否可以为 DSL 中的常量和表达式提供类型类?

问题描述

假设,我有一个带有计算的 DSL LangL r a。我可能想让函数同时使用常量(0 :: Int, "lala" :: String)和 DSL 表达式(LangL r a)。所以,我实现了一个类型类。但是,无论我尝试如何实现它,我都会遇到问题。

以下是使用类型族时出现问题的最小示例:

{-# LANGUAGE DeriveAnyClass        #-}
{-# LANGUAGE DeriveFunctor         #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE StandaloneDeriving    #-}
{-# LANGUAGE TypeFamilies          #-}

data LangL r a = LangL a
deriving instance Functor (LangL r)
deriving instance Applicative (LangL r)

class DSLEntity r a where
  type ValueOf a
  entityValue :: a -> LangL r (ValueOf a)

instance DSLEntity r (LangL r a) where
  type ValueOf (LangL r a) = a
  entityValue = id

instance DSLEntity r Int where
  type ValueOf Int = Int
  entityValue = pure

foo :: LangL r Int -> LangL r Int
foo m = entityValue (entityValue m)

GHC 给出以下输出:

    • Ambiguous type variable ‘r0’ arising from a use of ‘entityValue’
      prevents the constraint ‘(DSLEntity
                                  r (LangL r0 Int))’ from being solved.
      Relevant bindings include
        m :: LangL r Int (bound at temp.hs:25:5)
        foo :: LangL r Int -> LangL r Int
          (bound at temp.hs:25:1)
      Probable fix: use a type annotation to specify what ‘r0’ should be.
      These potential instance exist:
        instance DSLEntity r (LangL r a)
          -- Defined at temp.hs:16:10
    • In the expression: entityValue (entityValue m)
      In an equation for ‘foo’: foo m = entityValue (entityValue m)
   |
temp.hs:25:22-34: error: …
    • Ambiguous type variable ‘r0’ arising from a use of ‘entityValue’
      prevents the constraint ‘(DSLEntity
                                  r0 (LangL r Int))’ from being solved.
      Relevant bindings include
        m :: LangL r Int (bound at temp.hs:25:5)
        foo :: LangL r Int -> LangL r Int
          (bound at temp.hs:25:1)
      Probable fix: use a type annotation to specify what ‘r0’ should be.
      These potential instance exist:
        instance DSLEntity r (LangL r a)
          -- Defined at /temp.hs:16:10
    • In the first argument of ‘entityValue’, namely ‘(entityValue m)’
      In the expression: entityValue (entityValue m)
      In an equation for ‘foo’: foo m = entityValue (entityValue m)
   |

问题很清楚。r的参数LangL r ar参数之间没有依赖关系DSLEntity。但是,我们不能添加这样的依赖项,因为Int例如它实际上不存在。

我很困惑,想知道是否有可能完成我想做的事情。如果不是,为什么?

标签: haskelldslfunctional-dependenciestype-families

解决方案


您可以使用:

instance (r ~ r') => DSLEntity r' (LangL r a) where

代替:

instance DSLEntity r (LangL r a) where

这实际上做了什么有点神秘。

您最初的实例声明说 GHC 只能在可以证明 in 在参数和结果中的类型相同时使用rLangL r a实例entityValue。但是entityValue :: a -> LangL r (ValueOf a),因此任何类型都可以用作输入(并且需要 GHC 去寻找匹配的实例)。特别是, anyLangL r0 a可以作为输入出现,即使是 non-matching r。因此entityValue (entityValue m),第一个可以在任何地方使用r0,第二个会将其转换回rused 的类型foo。由于 GHC 无法确定您在中间谈论的是哪个,因此您会遇到不明确的类型变量阻止它知道应该选择哪个实例 来解决约束的问题。rDSLEntity

鉴于instance (r ~ r') => DSLEntity r' (LangL r a)此实例适用于任何类型rand ,但使用它会增加and相等r'的约束。这听起来和只是写一样,但实际上并不是因为 GHC 在选择实例时不考虑约束的规则,只是事后考虑。现在 GHC 不需要证明和相等来选择这个实例,它会在约束的第二个参数看起来像的任何时候选择实例,然后它会知道为了进行类型检查,约束必须保持,所以它会继续假设(如果可能的话;否则你会得到一个类型错误)。rr'instance DSLEntity r (LangL r a)rr'DSLEntityLangL _ _r ~ r'

通过查看 的类型,您可以很清楚地看到差异entityValue . entityValue。使用您的原始实例,您将获得:

λ :t entityValue . entityValue 
entityValue . entityValue
  :: (DSLEntity r1 (LangL r2 (ValueOf a)), DSLEntity r2 a) =>
     a -> LangL r1 (ValueOf a)

使用新实例,您会得到:

λ :t entityValue . entityValue 
entityValue . entityValue
  :: DSLEntity r a => a -> LangL r (ValueOf a)

推荐阅读