jjl*_*jjl 15 haskell effect-systems
我试图从基于变换器的monad堆栈重写一个简单的解释器到基于更自由的效果,但是我正在努力将我的意图传达给GHC的类型系统.
我目前只使用State和Fresh效果.我正在使用两种状态,我的效果运动员看起来像这样:
runErlish g ls = run . runGlobal g . runGensym 0 . runLexicals ls
where runGlobal = flip runState
runGensym = flip runFresh'
runLexicals = flip runState
Run Code Online (Sandbox Code Playgroud)
最重要的是,我已经使用以下类型定义了一个函数FindMacro:
findMacro :: Members [State (Global v w), State [Scope v w]] r
=> Arr r Text (Maybe (Macro (Term v w) v w))
Run Code Online (Sandbox Code Playgroud)
到目前为止所有这一切都完美无缺.当我尝试编写时出现问题macroexpand2(好吧,macroexpand1,但我正在简化它,所以问题更容易理解):
macroexpand2 s =
do m <- findMacro s
return $ case m of
Just j -> True
Nothing -> False
Run Code Online (Sandbox Code Playgroud)
这会产生以下错误:
Could not deduce (Data.Open.Union.Member'
(State [Scope v0 w0])
r
(Data.Open.Union.FindElem (State [Scope v0 w0]) r))
from the context (Data.Open.Union.Member'
(State [Scope v w])
r
(Data.Open.Union.FindElem (State [Scope v w]) r),
Data.Open.Union.Member'
(State (Global v w))
r
(Data.Open.Union.FindElem (State (Global v w)) r))
bound by the inferred type for `macroexpand2':
(Data.Open.Union.Member'
(State [Scope v w])
r
(Data.Open.Union.FindElem (State [Scope v w]) r),
Data.Open.Union.Member'
(State (Global v w))
r
(Data.Open.Union.FindElem (State (Global v w)) r)) =>
Text -> Eff r Bool
at /tmp/flycheck408QZt/Erlish.hs:(79,1)-(83,23)
The type variables `v0', `w0' are ambiguous
When checking that `macroexpand2' has the inferred type
macroexpand2 :: forall (r :: [* -> *]) v (w :: [* -> *]).
(Data.Open.Union.Member'
(State [Scope v w])
r
(Data.Open.Union.FindElem (State [Scope v w]) r),
Data.Open.Union.Member'
(State (Global v w))
r
(Data.Open.Union.FindElem (State (Global v w)) r)) =>
Text -> Eff r Bool
Probable cause: the inferred type is ambiguous
Run Code Online (Sandbox Code Playgroud)
好的,我可以Members在类型中添加注释:
macroexpand2 :: Members [State (Global v w), State [Scope v w]] r
=> Text -> Eff r Bool
Run Code Online (Sandbox Code Playgroud)
现在我明白了:
Overlapping instances for Member (State [Scope v0 w0]) r
arising from a use of `findMacro'
Matching instances:
instance Data.Open.Union.Member'
t r (Data.Open.Union.FindElem t r) =>
Member t r
-- Defined in `Data.Open.Union'
There exists a (perhaps superclass) match:
from the context (Members
'[State (Global v w), State [Scope v w]] r)
bound by the type signature for
macroexpand2 :: Members
'[State (Global v w), State [Scope v w]] r =>
Text -> Eff r Bool
at /tmp/flycheck408QnV/Erlish.hs:(79,17)-(80,37)
(The choice depends on the instantiation of `r, v0, w0'
To pick the first instance above, use IncoherentInstances
when compiling the other instance declarations)
In a stmt of a 'do' block: m <- findMacro s
In the expression:
do { m <- findMacro s;
return
$ case m of {
Just j -> True
Nothing -> False } }
In an equation for `macroexpand2':
macroexpand2 s
= do { m <- findMacro s;
return
$ case m of {
Just j -> True
Nothing -> False } }
Run Code Online (Sandbox Code Playgroud)
我被告知irc尝试forall r v w.哪个没有区别.出于好奇心,我IncoherentInstances在编译这段代码时尝试使用(我不喜欢查看更自由和播放的分支),看看是否会给我一个关于发生了什么的线索.它没:
Could not deduce (Data.Open.Union.Member'
(State [Scope v0 w0])
r
(Data.Open.Union.FindElem (State [Scope v0 w0]) r))
arising from a use of `findMacro'
from the context (Members
'[State (Global v w), State [Scope v w]] r)
bound by the type signature for
macroexpand2 :: Members
'[State (Global v w), State [Scope v w]] r =>
Text -> Eff r Bool
at /tmp/flycheck408eru/Erlish.hs:(79,17)-(80,37)
The type variables `v0', `w0' are ambiguous
Relevant bindings include
macroexpand2 :: Text -> Eff r Bool
(bound at /tmp/flycheck408eru/Erlish.hs:81:1)
Note: there are several potential instances:
instance (r ~ (t' : r'), Data.Open.Union.Member' t r' n) =>
Data.Open.Union.Member' t r ('Data.Open.Union.S n)
-- Defined in `Data.Open.Union'
instance (r ~ (t : r')) =>
Data.Open.Union.Member' t r 'Data.Open.Union.Z
-- Defined in `Data.Open.Union'
In a stmt of a 'do' block: m <- findMacro s
In the expression:
do { m <- findMacro s;
return
$ case m of {
Just j -> True
Nothing -> False } }
In an equation for `macroexpand2':
macroexpand2 s
= do { m <- findMacro s;
return
$ case m of {
Just j -> True
Nothing -> False } }
Run Code Online (Sandbox Code Playgroud)
所以,这是我对更自由的内部结构的理解用完了,我有疑问:
干杯!
And*_*ács 17
可扩展效应的类型推断在历史上是不好的.我们来看一些例子:
{-# language TypeApplications #-}
-- mtl
import qualified Control.Monad.State as M
-- freer
import qualified Control.Monad.Freer as F
import qualified Control.Monad.Freer.State as F
-- mtl works as usual
test1 = M.runState M.get 0
-- this doesn't check
test2 = F.run $ F.runState F.get 0
-- this doesn't check either, although we have a known
-- monomorphic state type
test3 = F.run $ F.runState F.get True
-- this finally checks
test4 = F.run $ F.runState (F.get @Bool) True
-- (the same without TypeApplication)
test5 = F.run $ F.runState (F.get :: F.Eff '[F.State Bool] Bool) True
Run Code Online (Sandbox Code Playgroud)
我将尝试解释一般问题并提供最少的代码说明.可以在此处找到代码的自包含版本.
在最基本的级别(忽略优化的表示),Eff定义如下:
{-# language
GADTs, DataKinds, TypeOperators, RankNTypes, ScopedTypeVariables,
TypeFamilies, DeriveFunctor, EmptyCase, TypeApplications,
UndecidableInstances, StandaloneDeriving, ConstraintKinds,
MultiParamTypeClasses, FlexibleInstances, FlexibleContexts,
AllowAmbiguousTypes, PolyKinds
#-}
import Control.Monad
data Union (fs :: [* -> *]) (a :: *) where
Here :: f a -> Union (f ': fs) a
There :: Union fs a -> Union (f ': fs) a
data Eff (fs :: [* -> *]) (a :: *) =
Pure a | Free (Union fs (Eff fs a))
deriving instance Functor (Union fs) => Functor (Eff fs)
Run Code Online (Sandbox Code Playgroud)
换句话说,Eff是一个来自仿函数列表的联合的免费monad.Union fs a表现得像n-ary Coproduct.二进制文件Coproduct就像Either两个仿函数:
data Coproduct f g a = InL (f a) | InR (g a)
Run Code Online (Sandbox Code Playgroud)
相比之下,Union fs a让我们从仿函数列表中选择一个仿函数:
type MyUnion = Union [[], Maybe, (,) Bool] Int
-- choose the first functor, which is []
myUnion1 :: MyUnion
myUnion1 = Here [0..10]
-- choose the second one, which is Maybe
myUnion2 :: MyUnion
myUnion2 = There (Here (Just 0))
-- choose the third one
myUnion3 :: MyUnion
myUnion3 = There (There (Here (False, 0)))
Run Code Online (Sandbox Code Playgroud)
让我们以State效果为例.首先,我们需要有一个Functor实例Union fs,因为Eff只有一个Monad实例if Functor (Union fs).
Functor (Union '[]) 是微不足道的,因为空联合没有值:
instance Functor (Union '[]) where
fmap f fs = case fs of {} -- using EmptyCase
Run Code Online (Sandbox Code Playgroud)
否则我们会在联盟中添加一个仿函数:
instance (Functor f, Functor (Union fs)) => Functor (Union (f ': fs)) where
fmap f (Here fa) = Here (fmap f fa)
fmap f (There u) = There (fmap f u)
Run Code Online (Sandbox Code Playgroud)
现在State定义和跑步者:
run :: Eff '[] a -> a
run (Pure a) = a
data State s k = Get (s -> k) | Put s k deriving Functor
runState :: forall s fs a. Functor (Union fs) => Eff (State s ': fs) a -> s -> Eff fs (a, s)
runState (Pure a) s = Pure (a, s)
runState (Free (Here (Get k))) s = runState (k s) s
runState (Free (Here (Put s' k))) s = runState k s'
runState (Free (There u)) s = Free (fmap (`runState` s) u)
Run Code Online (Sandbox Code Playgroud)
我们已经可以开始编写和运行我们的Eff程序,尽管我们缺乏所有的糖和便利:
action1 :: Eff '[State Int] Int
action1 =
Free $ Here $ Get $ \s ->
Free $ Here $ Put (s + 10) $
Pure s
-- multiple state
action2 :: Eff '[State Int, State Bool] ()
action2 =
Free $ Here $ Get $ \n -> -- pick the first effect
Free $ There $ Here $ Get $ \b -> -- pick the second effect
Free $ There $ Here $ Put (n < 10) $ -- the second again
Pure ()
Run Code Online (Sandbox Code Playgroud)
现在:
> run $ runState action1 0
(0,10)
> run $ (`runState` False) $ (`runState` 0) action2
(((),0),True)
Run Code Online (Sandbox Code Playgroud)
这里只有两个必不可少的缺失.
第一个是monad实例Eff,让我们使用do-notation代替Free和Pure,并且还允许我们使用许多多态monadic函数.我们将在这里跳过它,因为它写得很简单.
第二个是推理/重载,用于从效果列表中选择效果.以前我们需要编写Here x以选择第一个效果,There (Here x)选择第二个效果,依此类推.相反,我们想要在效果列表中编写多态的代码,因此我们必须指定的是,某些效果是列表的元素,而某些隐藏的类型类魔法将插入适当数量的There-s.
我们需要一个Member f fs类可以注入f a-s到Union fs a时-s f是的元素fs.从历史上看,人们已经以两种方式实施了它.
首先,直接用OverlappingInstances:
class Member (f :: * -> *) (fs :: [* -> *]) where
inj :: f a -> Union fs a
instance Member f (f ': fs) where
inj = Here
instance {-# overlaps #-} Member f fs => Member f (g ': fs) where
inj = There . inj
-- it works
injTest1 :: Union [[], Maybe, (,) Bool] Int
injTest1 = inj [0]
injTest2 :: Union [[], Maybe, (,) Bool] Int
injTest2 = inj (Just 0)
Run Code Online (Sandbox Code Playgroud)
第二,间接地,通过首先使用类型族计算fin 的索引fs,然后inj使用f-s computed index 引导的非重叠类来实现.这通常被视为更好,因为人们往往不喜欢重叠的实例.
data Nat = Z | S Nat
type family Lookup f fs where
Lookup f (f ': fs) = Z
Lookup f (g ': fs) = S (Lookup f fs)
class Member' (n :: Nat) (f :: * -> *) (fs :: [* -> *]) where
inj' :: f a -> Union fs a
instance fs ~ (f ': gs) => Member' Z f fs where
inj' = Here
instance (Member' n f gs, fs ~ (g ': gs)) => Member' (S n) f fs where
inj' = There . inj' @n
type Member f fs = Member' (Lookup f fs) f fs
inj :: forall fs f a. Member f fs => f a -> Union fs a
inj = inj' @(Lookup f fs)
-- yay
injTest1 :: Union [[], Maybe, (,) Bool] Int
injTest1 = inj [0]
Run Code Online (Sandbox Code Playgroud)
该freer库使用第二种解决方案,而extensible-effects第一种解决方案使用第一种解决方案,用于早于7.8的GHC版本,第二种解决方案用于较新的GHC-s.
无论如何,两种解决方案都有相同的推理限制,即我们几乎总是Lookup只能使用具体的单态类型,而不是包含类型变量的类型.ghci中的示例:
> :kind! Lookup Maybe [Maybe, []]
Lookup Maybe [Maybe, []] :: Nat
= 'Z
Run Code Online (Sandbox Code Playgroud)
这工作,因为那里是没有任何类型变量Maybe或者[Maybe, []].
> :kind! forall a. Lookup (Either a) [Either Int, Maybe]
forall a. Lookup (Either a) [Either Int, Maybe] :: Nat
= Lookup (Either a) '[Either Int, Maybe]
Run Code Online (Sandbox Code Playgroud)
这个因为a类型变量阻止减少而卡住了.
> :kind! forall a. Lookup (Maybe a) '[Maybe a]
forall a. Lookup (Maybe a) '[Maybe a] :: Nat
= Z
Run Code Online (Sandbox Code Playgroud)
这是有效的,因为我们对任意类型变量的唯一了解是它们等于它们自己,并且a等于a.
一般来说,类型族减少会卡在变量上,因为约束求解可能会在以后将它们精炼到不同类型,因此GHC不能对它们做任何假设(除了等于它们自己).基本上同样的问题出现在OverlappingInstances实现中(尽管没有任何类型的系列).
让我们freer根据这一点重新审视.
import Control.Monad.Freer
import Control.Monad.Freer.State
test1 = run $ runState get 0 -- error
Run Code Online (Sandbox Code Playgroud)
GHC知道我们有一个具有单一效果的堆栈,因为run有效Eff '[] a.它也知道这种效果必须如此State s.但是当我们编写时get,GHC只知道它对State t某些新t变量有影响,并且Num t必须保持,所以当它试图计算freer等价物时Lookup (State t) '[State s],它会卡在类型变量上,并且任何进一步的实例分辨率都会在卡住式家庭表达.另一个例子:
foo = run $ runState get False -- error
Run Code Online (Sandbox Code Playgroud)
这也失败了,因为GHC需要计算Lookup (State s) '[State Bool],虽然我们知道状态必须是Bool,但由于s变量,这仍然会卡住.
foo = run $ runState (modify not) False -- this works
Run Code Online (Sandbox Code Playgroud)
这是有效的,因为状态类型modify not可以解析为Bool,并Lookup (State Bool) '[State Bool]减少.
现在,经过这次大迂回之后,我将在你的帖子结尾处提出你的问题.
Overlapping instances并不表示任何可能的解决方案,只是一种类型错误工件.我需要更多的代码上下文来确定它究竟是如何产生的,但我确信它不相关,因为一旦Lookup卡住,案件就变得无望了.
IncoherentInstances也无关紧要,没有帮助.我们需要一个具体的效果位置索引才能为程序生成代码,如果Lookup卡住,我们就无法通过空气来拉动索引.
问题findMacro在于它State在状态内具有类型变量的效果.无论何时你想要使用,findMacro你必须确保v和w参数Scope和Global已知的具体类型.您可以通过键入注释来完成此操作,或者您可以更方便地使用TypeApplications和编写findMacro @Int @Int以指定v = Int和w = Int.如果您具有findMacro多态函数,则需要为该函数启用ScopedTypeVariables,绑定v和w使用forall v w.注释,并findMacro @v @w在使用时编写.您还需要启用{-# language AllowAmbiguousTypes #-}多态v或w(如注释中所指出的).我认为虽然在GHC 8中它是一个合理的扩展,与...一起启用TypeApplications.
附录:
然而,幸运的是,新的GHC 8功能让我们修复了可扩展效果的类型推断,我们可以推断出一切都mtl可以,而且有些东西mtl也无法处理.对于效果的排序,新类型推断也是不变的.
我在这里有一个最小的实现以及一些例子.但是,它还没有用在我所知道的任何效果库中.我可能会对它进行一次写作,然后执行拉取请求以将其添加到freer.