5

首先简要概述我的一般问题然后显示我卡在哪里可能更容易。

我想接收一些单例索引类型的 JSON 列表,其中索引类型也具有关联的类型族。在代码中:

data MyType = MyValue1 | MyValue2
type family MyFamily (mt :: MyType) where
    MyFamily MyValue1 = Int
    MyFamily MyValue2 = Double
data InputType (mt :: MyType) = InputNoFamily | InputWithFamily (MyFamily mt)
data OutputType (mt :: MyType) = OutputNoFamily | OutputWithFamily (MyFamily mt)

通过存在量化,我应该能够隐藏变化的索引并且仍然能够获得值(使用一些类似延续的更高级别的类型函数 - 可能有一个更好的名称)。我最终会按照以下方式运行我的程序

JSON -> [Some InputType] -> [Some OutputType] -> JSON

whereSome来自exinst包,但也在下面重新定义。在我不解析的情况下,我可以解析 JSON MyFamily mt,但我无法找到从 JSON 解析它的最佳方法。

到目前为止我所拥有的如下:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE RankNTypes #-}

module SO where

import Data.Aeson
import Data.Singletons.TH
import GHC.Generics

$(singletons [d|
  data MyType
    = MyValue1
    | MyValue2
    | MyValue3
    deriving (Show, Eq, Generic)
  |])
instance FromJSON MyType

type family MyFamily (mt :: MyType) :: * where
  MyFamily 'MyValue1 = Double
  MyFamily 'MyValue2 = Double
  MyFamily 'MyValue3 = Int

-- stolen from exinst package
data Some (f :: k -> *) =
    forall a. Some (Sing a) (f a)

some :: forall (f :: k -> *) a. SingI a => f a -> Some f
some = Some (sing :: Sing a)

withSome :: forall (f :: k -> *) (r :: *). Some f -> (forall a. SingI a => f a -> r) -> r
withSome (Some s x) g = withSingI s (g x)

data MyCompoundType (mt :: MyType)
    = CompoundNoIndex
    | CompoundWithIndex (MyFamily mt)

deriving instance (Show (SMyType mt), Show (MyFamily mt)) => Show (MyCompoundType mt)

-- instance with no parsing of `MyFamily`
instance
  forall (mt :: MyType).
  ( SingKind (KindOf mt)
  , FromJSON (DemoteRep (KindOf mt))
  ) => FromJSON (Some MyCompoundType) where
    parseJSON = withObject "MyCompoundType" $ \o -> do
      mt :: MyType <- o .: "myType"
      case toSing mt of
        SomeSing (smt :: SMyType mt') -> case smt of
          SMyValue1 -> return $ some (CompoundNoIndex :: MyCompoundType mt')
          SMyValue2 -> return $ some (CompoundNoIndex :: MyCompoundType mt')
          SMyValue3 -> return $ some (CompoundNoIndex :: MyCompoundType mt')

我显然需要添加一个FromJSON (MarketIndex mt)约束,但我还需要能够将它绑定到Some CompoundType我为其生成实例的那个。

简单添加一个FromJSON (MyFamily mt)约束

instance
  forall (mt :: MyType).
  ( SingKind (KindOf mt)
  , FromJSON (DemoteRep (KindOf mt))
  , FromJSON (MyFamily mt)
  ) => FromJSON (Some MyCompoundType) where
    parseJSON = undefined

给出模棱两可的类型错误

Could not deduce (FromJSON (MyFamily mt0))
  arising from the ambiguity check for an instance declaration
from the context (SingKind (KindOf mt),
                  FromJSON (DemoteRep (KindOf mt)),
                  FromJSON (MyFamily mt))
  bound by an instance declaration:
             (SingKind (KindOf mt), FromJSON (DemoteRep (KindOf mt)),
              FromJSON (MyFamily mt)) =>
             FromJSON (Some MyCompoundType)
  at SO.hs:(57,3)-(61,39)
The type variable ‘mt0’ is ambiguous
In the ambiguity check for:
  forall (mt :: MyType).
  (SingKind (KindOf mt), FromJSON (DemoteRep (KindOf mt)),
   FromJSON (MyFamily mt)) =>
  FromJSON (Some MyCompoundType)
To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
In the instance declaration for ‘FromJSON (Some (MyCompoundType))’

我可以看到类型检查器正在谈论mt0而不是mt一个大问题,但我不知道如何哄骗它mt在约束的右侧出现类型。

(我也意识到我没有包含FromJSON (MyFamily mt)实例,但如果类型检查器无法弄清楚mt ~ mt0我认为目前并不重要)。

希望有解决办法?

我花了相当多的时间尝试不同的事情,但有很多不同的事情发生(单身,存在主义等)。我正在慢慢地让自己达到一定的熟练程度,但我只是没有足够的知识或经验来确定他们是如何(或没有)促成这个问题的。

4

2 回答 2

2

我对单例不是很熟悉,但我仍然在这里发现了一个可能的误解:

在您当前的实例中,该部分

forall (mt :: MyType).
  ( SingKind (KindOf mt)
  , FromJSON (DemoteRep (KindOf mt))
  ) =>

根本不使用。如果您删除它,该文件也可以编译。

在我看来,您正试图设置一个约束,即“对于所有类型的 kind MyType,这些实例都应该存在。” 不幸的是,GHC 目前不支持这样的功能(有时称为“量化约束”或“秩 n 约束”)(并且 Simon PJ,他是第一个提出它的论文的合著者,在记录中说他不知道如何为其实现类型推断。)

我认为您的修改版本不起作用的原因是您实际上确实需要FromJSON (MyFamily mt)零件的量化约束。

不过,我有一种预感,希望能有所帮助。(不幸的是,我对使用单例编写实际的解决方案尝试了解得不够多。)如果您用 GADT 替换某些类型怎么办?例如:

data MyCompoundType (mt :: MyType) where
    CompoundNoIndex :: MyCompoundType mt
    CompoundWithIndex :: FromJSON (MyFamily mt) => MyCompoundType mt

这样,MyCompoundType可以随身携带所需的实例本身。

于 2015-10-08T18:51:02.743 回答
2

(我对您先前问题的先前回答在很大程度上适用于此)。

你可以自由地解析任何你想要的类型,你只需要证明一个特定的类型有一个FromJSON实例。在这种情况下,您应该解析 的具体结果类型MyFamily,因为它们都有适当的实例。

instance FromJSON (Some MyCompoundType) where
    parseJSON = withObject "MyCompoundType" $ \o -> do
      cons :: String <- o .: "constructor"
      mt :: MyType <- o .: "myType"
      case toSing mt of
        SomeSing smt ->
          case cons of
            "CompoundNoIndex" -> pure $ Some smt CompoundNoIndex
            "CompoundWithIndex" -> case smt of
              SMyValue1 -> Some SMyValue1 . CompoundWithIndex <$> o .: "field"
              SMyValue2 -> Some SMyValue2 . CompoundWithIndex <$> o .: "field"
              SMyValue3 -> Some SMyValue3 . CompoundWithIndex <$> o .: "field"

在这里,我假设有一些东西表明了编码的构造函数。当然,有许多用于编码和解码的替代格式。

或者,我们可以将量化约束的近似值放在一起,并更多地使用从该"myType"字段解析的单例标签:

import Data.Constraint -- from "constraints"
import Data.Proxy

data MyFamilySym :: TyFun MyType * -> *
type instance Apply MyFamilySym a = MyFamily a  

class ForallInst (f :: TyFun k * -> *) (c :: * -> Constraint) where
  allInst :: Proxy '(f, c) -> Sing x -> Dict (c (f @@ x))

instance ForallInst MyFamilySym FromJSON where
  allInst _ SMyValue1 = Dict
  allInst _ SMyValue2 = Dict
  allInst _ SMyValue3 = Dict  

instance FromJSON (Some MyCompoundType) where
    parseJSON = withObject "MyCompoundType" $ \o -> do
      cons :: String <- o .: "constructor"
      SomeSing smt <- toSing <$> o .: "myType"
      case cons of
        "CompoundNoIndex" -> pure (Some smt CompoundNoIndex)
        "CompoundWithIndex" ->
          case allInst (Proxy :: Proxy '(MyFamilySym, FromJSON)) smt of
            Dict -> Some smt . CompoundWithIndex <$> o .: "field" 

这里的关键点是用MyFamilySym和去功能化Apply。它使我们能够有效地将MyFamily实例头放入实例中,否则 GHC 将禁止这样做。有关. _ _singletons

对于类型族的量化实例,我们永远无法避免一件事:写出类型族的所有案例并为每个案例演示一个实例。解决方案也是这样做的ForallInst,但至少它要求我们只写一次案例。

于 2015-10-08T20:26:49.783 回答