3

我有这个带有状态单子的代码:

import Control.Monad.State

data ModelData = ModelData String
data ClientData = ClientData String

act :: String -> State ClientData a -> State ModelData a
act _ action = do
  let (result, _) = runState action $ ClientData ""
  return result

addServer :: String -> State ClientData ()
addServer _ = return ()

scenario1 :: State ModelData ()
scenario1 = do
  act "Alice" $ addServer "https://example.com"

我试图按照这种方法使用多态类型类来概括它:https ://serokell.io/blog/tagless-final 。

我可以概括 ModelData:

import Control.Monad.State

class Monad m => Model m where
  act :: String -> State c a -> m a

data Client = Client String

addServer :: String -> State Client ()
addServer _ = return ()

scenario1 :: Model m => m ()
scenario1 = do
  act "Alice" $ addServer "https://example.com"

但是,当我尝试同时使用 ModelData 和 ClientData 时,它无法编译:

module ExampleFailing where

class Monad m => Model m where
  act :: Client c => String -> c a -> m a

class Monad c => Client c where
  addServer :: String -> c ()

scenario1 :: Model m => m ()
scenario1 = do
  act "Alice" $ addServer "https://example.com"

错误:

    • Could not deduce (Client c0) arising from a use of ‘act’
      from the context: Model m
        bound by the type signature for:
                   scenario1 :: forall (m :: * -> *). Model m => m ()
        at src/ExampleFailing.hs:9:1-28
      The type variable ‘c0’ is ambiguous
    • In the expression: act "Alice"
      In a stmt of a 'do' block:
        act "Alice" $ addServer "https://example.com"
      In the expression:
        do act "Alice" $ addServer "https://example.com"
   |
11 |   act "Alice" $ addServer "https://example.com"
   |   ^^^^^^^^^^^

我可以用这种方式编译它,但它似乎与我试图概括的原始代码不同:

{-# LANGUAGE MultiParamTypeClasses #-}

module ExamplePassing where

class Monad m => Model m c where
  act :: Client c => String -> c a -> m (c a)

class Monad c => Client c where
  addServer :: String -> c ()

scenario1 :: (Client c, Model m c) => m (c ())
scenario1 = do
  act "Alice" $ addServer "https://example.com"

我非常感谢您的建议。谢谢!

4

1 回答 1

4

您的泛化尝试 withact :: Client c => String -> c a -> m a在技术上是正确的:它实际上是原始代码的翻译,但替换State ModelDatam和。State ClientDatac

发生错误是因为现在“客户端”可以是任何东西,调用者scenario1无法指定它应该是什么。

你看,为了确定addServer调用哪个版本,编译器必须知道是什么c,但无处可推断!c既不出现在函数参数中,也不出现在返回类型中。所以从技术上讲,它绝对可以是任何东西,它完全隐藏在里面scenario1。但是“绝对任何东西”对于编译器来说还不够好,因为选择c决定了调用哪个版本,addServer然后决定了程序的行为。

这是同一问题的较小版本:

f :: String -> String
f str = show (read str)

这同样不会编译,因为编译器不知道要调用哪个show版本read


你有几个选择。

首先,如果scenario1它自己知道要使用哪个客户端,它可以这样说TypeApplications

scenario1 :: Model m => m ()
scenario1 = do
  act "Alice" $ addServer @(State ClientData) "https://example.com"

其次, scenario1可以将此任务卸载给调用它的任何人。为此,您需要声明一个泛型变量c,即使它没有出现在任何参数或参数中。这可以通过以下方式完成ExplicitForAll

scenario1 :: forall c m. (Client c, Model m) => m ()
scenario1 = do
  act "Alice" $ addServer @c "https://example.com"

(请注意,您仍然需要@c让编译器知道addServer要使用哪个版本;要做到这一点,您需要ScopedTypeVariables,其中包括ExplicitForAll

然后消费者将不得不做这样的事情:

let server = scenario1 @(State ClientData)

最后,如果由于某种原因你不能使用TypeApplications, ExplicitForAll, or ScopedTypeVariables,你可以做同样事情的穷人版本 - 使用额外的虚拟参数来引入类型变量(这是以前的做法):

class Monad c => Client c where
  addServer :: Proxy c -> String -> c ()

scenario1 :: (Client c, Model m) => Proxy c -> m ()
scenario1 proxyC = do
  act "Alice" $ addServer proxyC "https://example.com"

(注意类方法本身现在也获得了一个哑参数;否则将再次无法调用它)

那么消费者将不得不做这件丑陋的事情:

let server = scenario1 (Proxy :: Proxy (State ClientData))
于 2020-03-22T14:10:43.697 回答