如何基于不相关的类型选择常量类型的值?



好的,所以我在想要进行更改之前得到了以下简化的工作示例:

data D = D
data C = C
class T a where
t :: a
instance T D where
t = D
instance T C where
t = C
g :: T a => IO a
g = do
return t
main = (g :: IO D) >> return ()

所以问题是,在g内部,我希望根据a选择不相关的a类型的值。换句话说,我想表达的是,如果aC则将选择尚未提及的e类型的某个值,如果不是,则将选择另一个类型为e的值。它基本上是对任意类型相等的条件化,就像伪代码if a ~ Bool then "foo" else "bar"一样。我像这样尝试过(在本例中对类型e使用String(:

{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
import Data.Proxy
class F sub1 sub2 where
f :: Proxy (sub1, sub2) -> String
instance {-# OVERLAPPABLE #-} F a b where
f _ = "did not match types"
instance {-# OVERLAPPING #-} F a a where
f _ = "matched types"
data D = D
data C = C
class T a where
t :: a
instance T D where
t = D
instance T C where
t = C
g :: forall a b. (T a, F b a) => IO a
g = do
putStrLn $ f (Proxy :: Proxy (D, a))
putStrLn $ f (Proxy :: Proxy (C, a))
return t
main = (g :: IO D) >> return ()

但是,我收到以下错误:

y.hs:30:14: error:
• Overlapping instances for F D a arising from a use of ‘f’
Matching instances:
instance [overlappable] F a b -- Defined at y.hs:10:31
instance [overlapping] F a a -- Defined at y.hs:13:30
(The choice depends on the instantiation of ‘a’
To pick the first instance above, use IncoherentInstances
when compiling the other instance declarations)
• In the second argument of ‘($)’, namely
‘f (Proxy :: Proxy (D, a))’
In a stmt of a 'do' block: putStrLn $ f (Proxy :: Proxy (D, a))
In the expression:
do putStrLn $ f (Proxy :: Proxy (D, a))
putStrLn $ f (Proxy :: Proxy (C, a))
return t
|
30 |   putStrLn $ f (Proxy :: Proxy (D, a))
|              ^^^^^^^^^^^^^^^^^^^^^^^^^
y.hs:31:14: error:
• Overlapping instances for F C a arising from a use of ‘f’
Matching instances:
instance [overlappable] F a b -- Defined at y.hs:10:31
instance [overlapping] F a a -- Defined at y.hs:13:30
(The choice depends on the instantiation of ‘a’
To pick the first instance above, use IncoherentInstances
when compiling the other instance declarations)
• In the second argument of ‘($)’, namely
‘f (Proxy :: Proxy (C, a))’
In a stmt of a 'do' block: putStrLn $ f (Proxy :: Proxy (C, a))
In the expression:
do putStrLn $ f (Proxy :: Proxy (D, a))
putStrLn $ f (Proxy :: Proxy (C, a))
return t
|
31 |   putStrLn $ f (Proxy :: Proxy (C, a))
|              ^^^^^^^^^^^^^^^^^^^^^^^^^
y.hs:34:9: error:
• Overlapping instances for F b0 D arising from a use of ‘g’
Matching instances:
instance [overlappable] F a b -- Defined at y.hs:10:31
instance [overlapping] F a a -- Defined at y.hs:13:30
(The choice depends on the instantiation of ‘b0’
To pick the first instance above, use IncoherentInstances
when compiling the other instance declarations)
• In the first argument of ‘(>>)’, namely ‘(g :: IO D)’
In the expression: (g :: IO D) >> return ()
In an equation for ‘main’: main = (g :: IO D) >> return ()
|
34 | main = (g :: IO D) >> return ()
|         ^

这些错误表明IncoherentInstances但它似乎不会选择正确的实例。我还没有想出一些新的东西来尝试。

编辑:只是为了看看会发生什么,我激活了IncoherentInstances,但它会导致相同的错误。

编辑2:我将解释该示例如何与我的实际场景相关联。g表示 HTML 表单。此窗体可以返回由T表示的不同类型。这些不同的类型使用表单中字段的不同子集。g中具有putStrLnf的行表示表单中字段的定义。f表示决定是否验证字段,具体取决于表单是否返回依赖于它的类型。

例如,表单可能返回类型DocSectionADocSectionB。一个字段可能是类型Text,我们想表达一个特定的字段应该只在表单返回DocSectionA时被验证,而另一个字段应该只在表单返回DocSectionB时被验证。

我希望这有所帮助。

我不明白你的T类是干什么用的。它似乎并没有以有趣/相关的方式实际使用。但是您的f可以使用对TypeRep的相等性检查来实现。例如:

{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
import Data.Type.Equality
import Type.Reflection
data C = C
data D = D
f :: forall a b. (Typeable a, Typeable b) => String
f = case testEquality (typeRep @a) (typeRep @b) of
Just Refl -> "matched"
_ -> "didn't match"
g :: forall a. Typeable a => IO ()
g = do
putStrLn (f @C @a)
putStrLn (f @D @a)
main = g @D

当然,您可以以通常的方式使用代理来避免ScopedTypeVariables和AllowAmbiguousType,如果这是您喜欢的方式。我使用了Typeable的新花式类型版本:虽然我们在上面没有使用它,但在f"matched"分支中,不仅我们,而且类型检查器也知道a ~ b

以下是我们现在使用不明确的类型和类型应用程序的方式。不明确的类型允许您拥有不提及类参数的类成员(否则可以使用代理(。

如果a ~ T,则c0,如果a ~ U1

{-# LANGUAGE AllowAmbiguousTypes, TypeApplications #-}
data T
data U
class C a where
c :: Int
instance C T where
c = 0
instance C U where
c = 1
main :: IO ()
main = print (c @T) >> print (c @U)

如果你真的想在aT的情况下匹配任何类型的类型(你为什么要这样做(,你可以使用重叠的实例(GHC手册是关于它们如何工作的最佳参考(:

{-# LANGUAGE FlexibleInstances #-} -- in addition to the above
instance {-# OVERLAPPABLE #-} C a where
c = 0
main = print (c @String)

相关内容

  • 没有找到相关文章

最新更新