首先简要概述我的一般问题然后显示我卡在哪里可能更容易。
我想接收一些单例索引类型的 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
我认为目前并不重要)。
希望有解决办法?
我花了相当多的时间尝试不同的事情,但有很多不同的事情发生(单身,存在主义等)。我正在慢慢地让自己达到一定的熟练程度,但我只是没有足够的知识或经验来确定他们是如何(或没有)促成这个问题的。