Dee*_*ant 8 monads haskell types variadic-functions typeclass
我正在尝试使用monadic返回类型创建一个可变参数函数,其参数也需要monadic上下文.(我不知道如何来形容第二点:例如,printf可以返回IO (),但在它是否最终被它的参数将被视为相同的不同IO ()或String).
基本上,我有一个数据构造函数,比如两个Char参数.我想提供两个指针样式ID Char参数,它可以State通过类型类实例从封闭的monad 自动解码.所以,get >>= \s -> foo1adic (Constructor (idGet s id1) (idGet s id2))我想做而不是做fooVariadic Constructor id1 id2.
接下来是我到目前为止所获得的文化Haskell样式,以防有人想复制它并弄乱它.
一,基本环境:
> {-# LANGUAGE FlexibleContexts #-}
> {-# LANGUAGE FlexibleInstances #-}
> {-# LANGUAGE MultiParamTypeClasses #-}
> import Control.Monad.Trans.State
> data Foo = Foo0
> | Foo1 Char
> | Foo2 Bool Char
> | Foo3 Char Bool Char
> deriving Show
> type Env = (String,[Bool])
> newtype ID a = ID {unID :: Int}
> deriving Show
> class InEnv a where envGet :: Env -> ID a -> a
> instance InEnv Char where envGet (s,_) i = s !! unID i
> instance InEnv Bool where envGet (_,b) i = b !! unID i
Run Code Online (Sandbox Code Playgroud)
一些测试数据为方便起见:
> cid :: ID Char
> cid = ID 1
> bid :: ID Bool
> bid = ID 2
> env :: Env
> env = ("xy", map (==1) [0,0,1])
Run Code Online (Sandbox Code Playgroud)
我有这个非monadic版本,它只是将环境作为第一个参数.这很好,但它不是我想要的.例子:
$ mkFoo env Foo0 :: Foo
Foo0
$ mkFoo env Foo3 cid bid cid :: Foo
Foo3 'y' True 'y'
Run Code Online (Sandbox Code Playgroud)
(我可以使用函数依赖或类型系列来摆脱对:: Foo类型注释的需要.现在我并不喜欢它,因为这不是我对它感兴趣的东西.)
> mkFoo :: VarC a b => Env -> a -> b
> mkFoo = variadic
>
> class VarC r1 r2 where
> variadic :: Env -> r1 -> r2
>
> -- Take the partially applied constructor, turn it into one that takes an ID
> -- by using the given state.
> instance (InEnv a, VarC r1 r2) => VarC (a -> r1) (ID a -> r2) where
> variadic e f = \aid -> variadic e (f (envGet e aid))
>
> instance VarC Foo Foo where
> variadic _ = id
Run Code Online (Sandbox Code Playgroud)
现在,我想要一个在以下monad中运行的可变参数函数.
> type MyState = State Env
Run Code Online (Sandbox Code Playgroud)
基本上,我不知道我该怎么做.我尝试用不同的方式表达类型类(variadicM :: r1 -> r2和variadicM :: r1 -> MyState r2)但是我没有成功编写实例.我也试过调整上面的非monadic解决方案,以便我以某种方式"结束",Env -> Foo然后我可以很容易地变成a MyState Foo,但也没有运气.
以下是我迄今为止最好的尝试.
> mkFooM :: VarMC r1 r2 => r1 -> r2
> mkFooM = variadicM
>
> class VarMC r1 r2 where
> variadicM :: r1 -> r2
>
> -- I don't like this instance because it requires doing a "get" at each
> -- stage. I'd like to do it only once, at the start of the whole computation
> -- chain (ideally in mkFooM), but I don't know how to tie it all together.
> instance (InEnv a, VarMC r1 r2) => VarMC (a -> r1) (ID a -> MyState r2) where
> variadicM f = \aid -> get >>= \e -> return$ variadicM (f (envGet e aid))
>
> instance VarMC Foo Foo where
> variadicM = id
>
> instance VarMC Foo (MyState Foo) where
> variadicM = return
Run Code Online (Sandbox Code Playgroud)
它适用于Foo0和Foo1,但不能超越:
$ flip evalState env (variadicM Foo1 cid :: MyState Foo)
Foo1 'y'
$ flip evalState env (variadicM Foo2 cid bid :: MyState Foo)
No instance for (VarMC (Bool -> Char -> Foo)
(ID Bool -> ID Char -> MyState Foo))
Run Code Online (Sandbox Code Playgroud)
(这里我想摆脱对注释的需求,但是这个公式需要两个实例的事实Foo会使问题变得复杂.)
我理解的抱怨:我只有从去一个实例Bool ->
Char -> Foo来ID Bool -> MyState (ID Char -> Foo).但我无法制作它想要的实例,因为我需要MyState在某处,以便我可以把它ID Bool变成一个Bool.
我不知道我是完全偏离轨道还是什么.我知道我可以用不同的方式解决我的基本问题(我不想用idGet s遍布各处的等价物污染我的代码),例如为不同数量的ID参数创建liftA/ liftM-style函数,类型如 (a -> b -> ... -> z -> ret) -> ID a -> ID b -> ... -> ID z -> MyState ret,但是我花了太多时间思考这个问题.:-)我想知道这个变量解决方案应该是什么样的.
警告
最好不要将可变参数函数用于此类工作。您只有有限数量的构造函数,因此智能构造函数似乎没什么大不了的。您需要的大约 10-20 行比可变参数解决方案更简单且更易于维护。此外,应用性解决方案的工作量要少得多。
警告
monad/applicative 与可变参数函数的结合就是问题所在。“问题”是用于可变参数类的参数添加步骤。基本类看起来像
class Variadic f where
func :: f
-- possibly with extra stuff
Run Code Online (Sandbox Code Playgroud)
通过使用表单实例使其成为可变参数
instance Variadic BaseType where ...
instance Variadic f => Variadic (arg -> f) where ...
Run Code Online (Sandbox Code Playgroud)
当你开始使用 monad 时,这会破坏。在类定义中添加 monad 将防止参数扩展(对于某些 monad M,您将得到 :: M (arg -> f))。将其添加到基本情况将阻止在扩展中使用 monad,因为(据我所知)不可能将 monad 约束添加到扩展实例。有关复杂解决方案的提示,请参阅 PS。
使用结果函数的解决方向(Env -> Foo)是更有前途的。以下代码仍然需要:: Foo类型约束,并为了简洁而使用 Env/ID 的简化版本。
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses, TypeFamilies #-}
module Test where
data Env = Env
data ID a = ID
data Foo
= Foo0
| Foo1 Char
| Foo2 Char Bool
| Foo3 Char Bool Char
deriving (Eq, Ord, Show)
class InEnv a where
resolve :: Env -> ID a -> a
instance InEnv Char where
resolve _ _ = 'a'
instance InEnv Bool where
resolve _ _ = True
Run Code Online (Sandbox Code Playgroud)
类型族扩展用于使匹配更严格/更好。现在是可变参数函数类。
class MApp f r where
app :: Env -> f -> r
instance MApp Foo Foo where
app _ = id
instance (MApp r' r, InEnv a, a ~ b) => MApp (a -> r') (ID b -> r) where
app env f i = app env . f $ resolve env i
-- using a ~ b makes this instance to match more easily and
-- then forces a and b to be the same. This prevents ambiguous
-- ID instances when not specifying there type. When using type
-- signatures on all the ID's you can use
-- (MApp r' r, InEnv a) => MApp (a -> r') (ID a -> r)
-- as constraint.
Run Code Online (Sandbox Code Playgroud)
环境Env是显式传递的,实质上Readermonad 被解包,防止 monad 和可变参数函数之间出现问题(对于 monad,State解析函数应该返回一个新环境)。测试app Env Foo1 ID :: Foo结果符合预期Foo1 'a'。
PS 你可以让一元可变参数函数工作(在某种程度上),但它需要以一些非常奇怪的方式弯曲你的函数(和思想)。我让这些事情发挥作用的方法是将所有可变参数“折叠”到一个异构列表中。然后可以以单体方式进行解包。尽管我已经做了一些类似的事情,但我强烈建议您不要在实际(使用过的)代码中使用此类内容,因为它很快就会变得难以理解和无法维护(更不用说您会遇到的类型错误)。