所以当我遇到这种类型的错误时,我正在玩可扩展效果试图重新实现一些基本类型和函数:
home/kadhem/projects/Haskell/stackWorkingAgain/app/Implementation_error.hs:24:96: error:
* Couldn't match type `x1' with `x'
`x1' is a rigid type variable bound by
a pattern with constructor:
Impure :: forall (r :: [* -> *]) a x.
Union r x -> (x -> Eff r a) -> Eff r a,
in an equation for `createInterpreter'
at /home/kadhem/projects/Haskell/stackWorkingAgain/app/Implementation_error.hs:22:59-68
`x' is a rigid type variable bound by
the type signature for:
createInterpreter :: forall a (r :: [* -> *]) b (f :: * -> *) x.
(a -> Eff r b)
-> (f x -> (x -> Eff (f : r) a) -> Eff (f : r) a)
-> (Eff r b -> Eff r b)
-> Eff (f : r) a
-> Eff r b
at /home/kadhem/projects/Haskell/stackWorkingAgain/app/Implementation_error.hs:(15,1)-(18,47)
Expected type: f x
Actual type: f x1
* In the first argument of `runContinuation', namely
`f_is_theTarget'
我不明白x1是如何被构造函数Impure绑定的。
这是完整的代码:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GADTSyntax #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeOperators #-}
module Implemntation where
import Data.OpenUnion (Union , decomp)
data Eff r a where
Pure :: a -> Eff r a
Impure :: Union r x -> (x -> Eff r a) -> Eff r a
createInterpreter :: (a -> Eff r b)
-> (f x -> (x -> Eff (f ': r) a) -> Eff (f ': r) a)
-> (Eff r b -> Eff r b)
-> Eff (f ': r) a -> Eff r b
createInterpreter handlePure runContinuation applyEffect (Pure a) =
handlePure a
createInterpreter handlePure runContinuation applyEffect (Impure f k)
= case decomp f of
Right f_is_theTarget
-> applyEffect $ createInterpreter handlePure runContinuation
applyEffect (runContinuation f_is_theTarget k)
Left f_is_notTheTarget
-> Impure f_is_notTheTarget $ createInterpreter handlePure
runContinuation applyEffect . k
答案 0 :(得分:3)
考虑以下两个事实:
事实1:无论是谁调用Impure
,都可以选择其类型中x
的类型:
Impure :: Union r x -> (x -> Eff r a) -> Eff r a
请注意,此类x
不会在Eff r a
中结束,从而使该类型成为"存在主义"之一。
事实2:任何调用createInterpreter
的人都可以在其类型中选择x
的值
createInterpreter :: (a -> Eff r b)
-> (f x -> (x -> Eff (f ': r) a) -> Eff (f ': r) a)
-> (Eff r b -> Eff r b)
-> Eff (f ': r) a -> Eff r b
请注意,这个选择是独立来自第一个选择!
所以,这些事实都暗示我们打电话时
createInterpreter handlePure runContinuation applyEffect (Impure f k)
我们可以为runContinuation
类型传递x
函数,并使用不同类型Impure
(例如x
)传递x1
。由于您尝试混合使用这些类型,编译器会抱怨它们不必相同。
您可能需要以下类型
createInterpreter :: (a -> Eff r b)
-> (forall x. f x -> (x -> Eff (f ': r) a) -> Eff (f ': r) a)
-> (Eff r b -> Eff r b)
-> Eff (f ': r) a -> Eff r b
这将迫使您稍后传递一个多态 runContinuation
函数,该函数适用于任何可能找到的x
"内部" Impure
。
您的示例非常复杂,但要了解此问题,您还可以考虑类似的情况:
data SomeList where
SL :: [x] -> SomeList
sumIntList :: [Int] -> Int
sumIntList = sum
workWithSL :: ([x] -> Int) -> SomeList -> Int
workWithSL f (SL list) = f list
test :: Int
test = workWithSL sumIntList (SL [True, False])
此处,我们在调用x = Bool
时选择SL
,但在调用x = Int
时我们选择workWithSL
(因为我们通过了sumIntList
)。这种调用没有任何问题,因为类型完全检查。真正的问题是在workWithSL
内,f
无法应用list
,因为list
可能属于[x1]
而不是[x]
。