I'm developing a framework for running experiments with artificial life, and I'm trying to use type families instead of functional dependencies. Type families seems to be the preferred approach among Haskellers, but I've run into a situation where functional dependencies seem like a better fit. Am I missing a trick? Here's the design using type families. (This code compiles OK.)
{-# LANGUAGE TypeFamilies, FlexibleContexts #-}
import Control.Monad.State (StateT)
class Agent a where
agentId :: a -> String
liveALittle :: Universe u => a -> StateT u IO a
-- plus other functions
class Universe u where
type MyAgent u :: *
withAgent :: (MyAgent u -> StateT u IO (MyAgent u)) ->
String -> StateT u IO ()
-- plus other functions
data SimpleUniverse = SimpleUniverse
{
mainDir :: FilePath
-- plus other fields
}
defaultWithAgent :: (MyAgent u -> StateT u IO (MyAgent u)) -> String ->
StateT u IO ()
defaultWithAgent = undefined -- stub
-- plus default implementations for other functions
--
-- In order to use my framework, the user will need to create a typeclass
-- that implements the Agent class...
--
data Bug = Bug String deriving (Show, Eq)
instance Agent Bug where
agentId (Bug s) = s
liveALittle bug = return bug -- stub
--
-- .. and they'll also need to make SimpleUniverse an instance of Universe
-- for their agent type.
--
instance Universe SimpleUniverse where
type MyAgent SimpleUniverse = Bug
withAgent = defaultWithAgent -- boilerplate
-- plus similar boilerplate for other functions
Is there a way to avoid forcing my users to write those last two lines of boilerplate? Compare with the version using fundeps, below, which seems to make things simpler for my users. (The use of UndecideableInstances may be a red flag.) (This code also compiles OK.)
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances,
UndecidableInstances #-}
import Control.Monad.State (StateT)
class Agent a where
agentId :: a -> String
liveALittle :: Universe u a => a -> StateT u IO a
-- plus other functions
class Universe u a | u -> a where
withAgent :: Agent a => (a -> StateT u IO a) -> String -> StateT u IO ()
-- plus other functions
data SimpleUniverse = SimpleUniverse
{
mainDir :: FilePath
-- plus other fields
}
instance Universe SimpleUniverse a where
withAgent = undefined -- stub
-- plus implementations for other functions
--
-- In order to use my framework, the user will need to create a typeclass
-- that implements the Agent class...
--
data Bug = Bug String deriving (Show, Eq)
instance Agent Bug where
agentId (Bug s) = s
liveALittle bug = return bug -- stub
--
-- And now my users only have to write stuff like...
--
u :: SimpleUniverse
u = SimpleUniverse "mydir"
Edit: In trying to present a simple example, I omitted part of the motivation for my design.
The #1 role that the Universe class plays is serialising and deserialising agents, so I think it has to be linked to the Agent class. It also has readAgent
and writeAgent
functions. However, I wanted to ensure that the user couldn't accidentally forget to write an agent after modifying it, so instead of exporting those functions, I provide a withAgent
function that takes care of everything. The withAgent
function takes two parameters: a function that runs on an agent, and the name (unique ID) of the agent to run the program on. It reads the file containing that agent, runs the program, and writes the updated agent back out to the file. (I could instead just export the readAgent and writeAgent functions.)
There is also a Daemon
class that is responsible for giving each agent its fair share of the CPU. So inside the daemon's main loop, it queries the universe for a current list of agents. Then, for each agent, it invokes the withAgent
function to run the liveAlittle
program for that agent. The daemon doesn't care what type the agent is.
There is one other user of the withAgent
function: the agent itself. Inside the agent's liveALittle
function, it might query the universe for a list of agents, in order a possible mating partner. It will invoke the withAgent
function to run some sort of mating function. Obviously an agent can only mate with another agent of the same species (typeclass).
EDIT: Here's the solution I think I will use. Not type families or functional dependencies, but now I have to do something so that the compiler will know which liveALittle
to call. The way I've done that is to have the user supply the correct liveALittle
as a parameter.
{-# LANGUAGE DeriveGeneric #-}
import Control.Monad.State (StateT)
import Data.Serialize (Serialize)
import GHC.Generics (Generic)
class Agent a where
agentId :: a -> String
liveALittle :: Universe u => a -> StateT u IO a
-- plus other functions
class Universe u where
-- Given the name of an agent, read it from a file, and let it run.
withAgent :: (Agent a, Serialize a) =>
(a -> StateT u IO a) -> String -> StateT u IO ()
-- plus other functions
-- This method will be called by a daemon
daemonTask :: (Universe u, Agent a, Serialize a) =>
(a -> StateT u IO a) -> StateT u IO ()
daemonTask letAgentLiveALittle = do
-- do some stuff
withAgent letAgentLiveALittle "a"
-- do some other stuff
data SimpleUniverse = SimpleUniverse
{
mainDir :: FilePath
-- plus other fields
}
instance Universe SimpleUniverse where
withAgent = undefined -- stub
-- plus implementations for other functions
--
-- And now my users only have to write stuff like...
--
data Bug = Bug String deriving (Show, Eq, Generic)
instance Serialize Bug
instance Agent Bug where
agentId (Bug s) = s
liveALittle bug = return bug -- stub
I think that you are overcomplicating things. It's not more complicated to support every kind of actor in a universe, it's less complicated.
Just write your Universe
class like so:
class Universe u where
withAgent :: Agent a => (a -> StateT u IO a) -> String -> StateT u IO ()
Note that you don't have to use functional dependencies or multi-param type classes, because the a
doesn't have to be brought into scope in the class head; it is brought into scope by Agent a => ...
. This is also essentially what you are doing in your functionally dependent version, because even though you use u a | u -> a
, that a
doesn't actually get used in the class body; instead, the Agent a => ...
shadows the outer a
.