我正在开发人工生命实验的框架。该框架可以支持多个物种,只要每个物种都是代理类的一个实例。我将每个 Agent 包装在一个 AgentBox 中,这样我就可以在不知道底层类型的情况下读取、写入和使用它们。
这很好用,但是框架的用户必须编写一个小的样板函数。我很想知道是否有办法避免这种情况。我无法在 Agent 类中提供该函数的默认实现,因为该函数的类型签名没有提及类型变量。我可以忍受样板,但我很想知道是否有更好的方法。
这是我正在谈论的最小工作示例。最后的 getRock 函数是我希望避免强迫我的用户编写的函数。Agent 类的每个实例都需要提供一个函数来读取代理并将其包装在一个盒子中,并且实现看起来总是与 getRock 完全一样。
{-# LANGUAGE ExistentialQuantification, DeriveGeneric #-}
import qualified Data.Serialize as DS (Get, Serialize, get, put)
import Data.Serialize.Put (PutM)
import Data.List (find)
import Data.Maybe (fromJust, isNothing)
import GHC.Generics ( Generic )
class Agent a where
agentId :: a -> String
speciesId :: a -> String
-- other functions to be added
-- This wrapper allows me to use Agents without knowing their type.
data AgentBox = forall a. (DS.Serialize a, Agent a) => AgentBox a
-- Instructions for deserialising an agent
data ReaderSpec = ReaderSpec { tag :: String, getter :: DS.Get AgentBox }
-- Serialise an AgentBox by putting the species tag, then the agent.
putAgentBox :: AgentBox -> PutM ()
putAgentBox (AgentBox a) = do
DS.put $ speciesId a
DS.put a
-- Deserialise an agent by getting the species tag, looking up the getter
-- for that species of agent, and then getting the agent itself.
getAgentBox :: [ReaderSpec] -> DS.Get (Either String AgentBox)
getAgentBox xs = do
s <- DS.get :: DS.Get String
let a = find (\x -> tag x == s) xs
if isNothing a
then return $ Left $ "No getter found for " ++ s
else do
let d = (getter . fromJust) a
t <- d
return $ Right t
--
-- Everything above this line is provided by the framework.
-- The user of the framework would create their own instances of the class
-- Agent, by writing something like this:
--
data Rock = Rock String Int deriving (Show, Generic)
rockTag :: String
rockTag = "Rock"
readerSpec :: ReaderSpec
readerSpec = ReaderSpec rockTag getRock
instance Agent Rock where
agentId (Rock name _) = name
speciesId _ = rockTag
-- other functions to be added
instance DS.Serialize Rock
-- | Get the agent and wrap it in a box.
getRock :: DS.Get AgentBox
getRock = do
t <- DS.get :: DS.Get Rock
return $ AgentBox t