问题
I have this code with State monads:
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"
I am trying to generalise it with polymorphic type-classes following this approach: https://serokell.io/blog/tagless-final.
I can generalise 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"
But when I try to do it with both ModelData and ClientData it fails to compile:
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"
The error:
• 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"
| ^^^^^^^^^^^
I can make it compile this way, but it seems different from the original code I am trying to generalise:
{-# 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"
I would really appreciate your advice. Thank you!
回答1:
Your generalization attempt with act :: Client c => String -> c a -> m a
is technically correct: it's literally a translation of the original code, but replacing State ModelData
with m
and State ClientData
with c
.
The error happens because now that the "client" can be anything, the caller of scenario1
has no way to specify what it should be.
You see, in order to determine which version of addServer
to call, the compiler has to know what c
is, but there is nowhere to infer that from! c
appears neither in the function parameters nor in return type. So technically it can be absolutely anything, it's completely hidden inside scenario1
. But "absolutely anything" isn't good enough for the compiler, because the choice of c
determines which version of addServer
is called, which will then determine the program behavior.
Here's a smaller version of the same problem:
f :: String -> String
f str = show (read str)
This will similarly not compile because the compiler doesn't know which versions of show
and read
to call.
You have a few options.
First, if scenario1
itself knows which client to use, it can say so by using TypeApplications
:
scenario1 :: Model m => m ()
scenario1 = do
act "Alice" $ addServer @(State ClientData) "https://example.com"
Second, scenario1
can offload this task onto whoever calls it. To do that, you need to declare a generic variable c
even though it doesn't appear in any parameters or arguments. This can be done with ExplicitForAll
:
scenario1 :: forall c m. (Client c, Model m) => m ()
scenario1 = do
act "Alice" $ addServer @c "https://example.com"
(note that you still have to do @c
to let the compiler know which version of addServer
to use; to be able to do this, you'll need ScopedTypeVariables
, which includes ExplicitForAll
)
Then the consumer will have to do something like this:
let server = scenario1 @(State ClientData)
Finally, if for some reason you cannot use TypeApplications
, ExplicitForAll
, or ScopedTypeVariables
, you can do the poor man's version of the same thing - use an extra dummy parameter to introduce the type variable (this is how it was done in the before times):
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"
(note that the class method itself has now also acquired a dummy parameter; otherwise there will again be no way to call it)
Then the consumer will have to do this ugly thing:
let server = scenario1 (Proxy :: Proxy (State ClientData))
来源:https://stackoverflow.com/questions/60800042/two-polymorphic-classes-in-one-function