我正在尝试定义一种可以限制为Nat
子集的类型。虽然我意识到一个简单的解决方案是使用常规ADT,但我仍然很好奇,如果可以使用附带的FromJSON
实例来定义这种类型。这是我到目前为止所做的:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Test where
import Control.Monad
import Data.Aeson
import Data.Kind (Constraint)
import Data.Proxy
import Data.Type.Equality
import GHC.TypeLits
import Prelude
type family Or (a :: Bool) (b :: Bool) :: Bool where
Or 'False 'False = 'False
Or 'True 'False = 'True
Or 'False 'True = 'True
Or 'True 'True = 'True
type family IsOneOf (n :: Nat) (xs :: [Nat]) :: Bool where
IsOneOf n '[] = 'False
IsOneOf n (x ': xs) = Or (n == x) (IsOneOf n xs)
type family Member n xs :: Constraint where
Member n xs = 'True ~ IsOneOf n xs
data SomeEnum (xs :: [Nat]) where
SomeEnum :: (KnownNat n, Member n xs) => Proxy n -> SomeEnum xs
然后可以按如下方式使用:
λ> SomeEnum (Proxy :: Proxy 1) :: SomeEnum [1,2]
我能够定义ToJSON
实例:
instance ToJSON (SomeEnum xs) where
toJSON (SomeEnum n) = Number (fromIntegral . natVal $ n)
然而,它似乎没有声明FromJSON
实例是可能的,因为我无法弄清楚如何说服编译器我可能从JSON文档获得的任何数字确实是该组的成员接受的值为SomeEnum
。
我的问题是 - 是否可以根据数据类型的当前公式声明该实例?也许类型本身可以某种方式进行调整以允许这样的实例,同时保留被限制为特定Nat
s集的行为?
我对Haskell的类型级别功能不是很熟悉,所以也许我所问的内容在当前形式中没有意义。我将不胜感激。
答案 0 :(得分:2)
在不分散JSON的情况下查看问题会更容易。
真正的问题是你可以定义一个函数
toSomeEnum :: Integer -> SomeEnum xs
由于SomeEnum []
与Void
同构,-1
无法转换为SomeEnum xs
任何xs
toSomeEnum :: Integer -> Maybe (SomeEnum xs)
,显然不是。我们需要失败的能力:
const Nothing
要做除xs
以外的任何事情,我们需要能够比较。{1}}
toSomeEnum' :: forall xs. ToSomeEnum xs => Integer -> Maybe (SomeEnum xs)
toSomeEnum' n = do
SomeNat proxy_n <- someNatVal n
toSomeEnum proxy_n
class ToSomeEnum (xs :: [Nat]) where
toSomeEnum :: forall (n :: Nat). KnownNat n => Proxy n -> Maybe (SomeEnum xs)
instance ToSomeEnum '[] where
toSomeEnum = const Nothing
instance (KnownNat x, ToSomeEnum xs) => ToSomeEnum (x ': xs) where
toSomeEnum proxy_n = case sameNat proxy_n (Proxy @x) of
Just Refl -> Just (SomeEnum proxy_n) -- [1]
Nothing -> case toSomeEnum proxy_n :: Maybe (SomeEnum xs) of
Nothing -> Nothing
Just (SomeEnum proxy_n') -> Just (SomeEnum proxy_n') -- [2]
到运行时输入的元素:
• Could not deduce: Or 'True (IsOneOf n xs) ~ 'True
arising from a use of ‘SomeEnum’
from the context: x ~ n
bound by a pattern with constructor:
Refl :: forall k (a :: k). a :~: a,
in a case alternative
at [1]
...
• Could not deduce: Or (GHC.TypeLits.EqNat n1 x) 'True ~ 'True
arising from a use of ‘SomeEnum’
from the context: (KnownNat n1, Member n1 xs)
bound by a pattern with constructor:
SomeEnum :: forall (xs :: [Nat]) (n :: Nat).
(KnownNat n, Member n xs) =>
Proxy n -> SomeEnum xs,
in a case alternative
at [2]
这并没有因为GHC抱怨而完全工作
Or
可以使用type family Or (a :: Bool) (b :: Bool) :: Bool where
Or 'True _ = 'True
Or _ 'True = 'True
Or _ _ = 'False
:
unsafeCoerce
不需要xs
或输入证人。你的调用代码只需要
知道它期望的λ case (toSomeEnum' 1 :: Maybe (SomeEnum '[1,2,3])) of { Just _ -> "ok" ; Nothing -> "nope" }
"ok"
λ case (toSomeEnum' 4 :: Maybe (SomeEnum '[1,2,3])) of { Just _ -> "ok" ; Nothing -> "nope" }
"nope"
。
{{1}}