簡體   English   中英

一個函數中的兩個多態類

[英]Two polymorphic classes in one function

我有這個帶有 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"

我試圖按照這種方法用多態類型類來概括它: 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"

我真的很感激你的建議。 謝謝!

您對act :: Client c => String -> ca -> ma泛化嘗試在技術上是正確的:它實際上是原始代碼的翻譯,但將State ModelData替換為m並將State ClientData替換為c

發生錯誤是因為現在“客戶端”可以是任何東西, scenario1的調用者無法指定它應該是什么。

你看,為了確定要調用哪個版本的addServer ,編譯器必須知道c是什么,但無處可推! c既沒有出現在函數參數中,也沒有出現在返回類型中。 所以從技術上講,它可以是任何東西,它完全隱藏在scenario1 但是“絕對任何”對於編譯器來說還不夠好,因為c的選擇決定了調用addServer哪個版本,然后決定了程序的行為。

這是同一問題的較小版本:

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

這同樣不會編譯,因為編譯器不知道要調用哪個版本的showread


你有幾個選擇。

首先,如果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)

最后,如果由於某種原因,你不能使用TypeApplicationsExplicitForAll ,或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))

暫無
暫無

聲明:本站的技術帖子網頁,遵循CC BY-SA 4.0協議,如果您需要轉載,請注明本站網址或者原文地址。任何問題請咨詢:yoyou2525@163.com.

 
粵ICP備18138465號  © 2020-2024 STACKOOM.COM