Question

I'm developing a framework for artificial life experiments. The framework can support multiple species, as long as each species is an instance of the Agent class. I wrap each Agent in an AgentBox so that I can read, write, and use them without knowing the underlying type.

This works well, but there is one small boilerplate function that the user of the framework has to write. I'm interested in knowing if there's a way to avoid this. I can't supply a default implementation of that function in the Agent class, because the type signature of the function doesn't mention the type variable. I can live with the boilerplate, but I'm very curious to know if there's a better way.

Here's a minimum working example of what I'm talking about. The getRock function at the very end is the one that I'd like to avoid forcing my users to write. Every instance of the class Agent will need to supply a function that reads the agent and wraps it in a box, and the implementations will always look exactly like 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
Was it helpful?

Solution

You can write a function to create ReaderSpecs for any given type a, almost like so:

-- Create a 'ReaderSpec' that deserializes objects of type 'a'
mkReaderSpec :: (DS.Serialize a, Agent a) => String -> ReaderSpec

Since a doesn't appear in the parameters or return types, it's necessary to pass a proxy for the type as an extra parameter. Typically that's done by passing an undefined value. Expressions are forced to have type a by calling asTypeOf.

-- Create a 'ReaderSpec' that deserializes objects of type 'a'
mkReaderSpec :: (DS.Serialize a, Agent a) => String -> a -> ReaderSpec
mkReaderSpec tag dummy = ReaderSpec tag getter
  where
    getter = do {t <- DS.get; return $ AgentBox (t `asTypeOf` dummy)}

Now the framework can make ReaderSpecs for any given type. The user selects a type and associated class instances by passing in undefined.

readerSpec = mkReaderSpec "Rock" (undefined :: Rock)
Licensed under: CC-BY-SA with attribution
Not affiliated with StackOverflow
scroll top