Resolving ambiguity in MultiParameterTypeClass - haskell

Based on the feedback to this question, I've used a MultiParamTypeClass to represent a reinforcement learning environment Environment, using 3 type variables: e for the environment instance itself (e.g. a game like Nim, below), s for the state data type used by the specific game, and a for the action data type used by the specific game.
{-# LANGUAGE MultiParamTypeClasses #-}
class MultiAgentEnvironment e s a where
baseState :: e -> s
nextState :: e -> s -> a -> s
reward :: (Num r) => e -> s -> a -> [r]
data Game = Game { players :: Int
, initial_piles :: [Int]
} deriving (Show)
data State = State { player :: Int
, piles :: [Int]} deriving (Show)
data Action = Action { removed :: [Int]} deriving (Show)
instance MultiAgentEnvironment Game State Action where
baseState game = State{player=0, piles=initial_piles game}
nextState game state action = State{player=player state + 1 `mod` players game,
piles=zipWith (-) (piles state) (removed action)}
reward game state action = [0, 0]
newGame :: Int -> [Int] -> Game
newGame players piles = Game{players=players, initial_piles=piles}
main = do
print "Hello, world!"
let game = newGame 2 [3,4,5]
print game
As expected, I'm running into ambiguity issues already. See below, where the action type variable a is deemed ambiguous within the typeclass Environment.
(base) randm#soundgarden:~/Projects/games/src/Main$ ghc -o basic basic.hs
[1 of 1] Compiling Main ( basic.hs, basic.o )
basic.hs:4:5: error:
• Could not deduce (MultiAgentEnvironment e s a0)
from the context: MultiAgentEnvironment e s a
bound by the type signature for:
baseState :: forall e s a. MultiAgentEnvironment e s a => e -> s
at basic.hs:4:5-23
The type variable ‘a0’ is ambiguous
• In the ambiguity check for ‘baseState’
To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
When checking the class method:
baseState :: forall e s a. MultiAgentEnvironment e s a => e -> s
In the class declaration for ‘MultiAgentEnvironment’
|
4 | baseState :: e -> s
| ^^^^^^^^^^^^^^^^^^^
How do I resolve this ambiguity? Am I mistakenly using typeclasses to implement interfaces (i.e. baseState, nextState, reward)?

While you could turn on AllowAmbiguousTypes, that will only push your problem further down the road. That is, eventually, you'll try to call baseState, and GHC will need to know what a is. There are three good options you have:
Use functional dependencies,
Use associated type families, or
Don't use a class for this.
Let's look at each option in detail.
Functional Dependencies
The problem that GHC is having is that it knows which e and s you want to use when you call a function like baseState (it can determine those from the input and output of the baseState function), but it doesn't know which a to use. For all GHC knows, there may be multiple instantiations of MultiAgentEnvironment that could work for a given e and s. With functional dependencies, you can tell GHC that a given e and s totally define what the a should be. In plain English, by putting in a functional dependency on a, you're saying that for any given environment and state, there is only one possible action type that makes sense. If this is true, then you add them like so:
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
class MultiAgentEnvironment e s a | e s -> a where
baseState :: e -> s
nextState :: e -> s -> a -> s
reward :: (Num r) => e -> s -> a -> [r]
Since each one of your functions have e and s in them, a is the only type parameter that could have been ambiguous, and with this fundep, it's not ambiguous anymore. That said, if you know that the environment type determines both the state and action unambiguously (that is, a given environment can only ever have one possible state and action type), then you can use two fundeps to lower the ambiguity even more, as in:
class MultiAgentEnvironment e s a | e -> s a where
Associated Type Families
Functional Dependencies have a bit of a bad reputation, and the more modern alternative is typically to use associated type families. In practice, for your purposes, they work very similarly. Once again, you have to be okay with the environment type determining the action type (and, perhaps, the state type). If so, you write it like this:
{-# LANGUAGE TypeFamilies #-}
class MultiAgentEnvironment e where
type EState e
type EAction e
baseState :: e -> EState e
nextState :: e -> EState e -> a -> EState e
reward :: (Num r) => e -> EState e -> EAction e -> [r]
Then, when you create your instance, it will look like:
instance MultiAgentEnvironment Game where
type EState Game = State
type EAction Game = Action
baseState game = State{player=0, piles=initial_piles game}
nextState game state action = ...
Use a Data Type Instead Of a Class
The last option is to forgo using a type class altogether. Instead, you can make the data explicit by just representing it as a data type. For instance, you can define:
{-# LANGUAGE RankNTypes #-}
data MultiAgentEnvironment e s a = MultiAgentEnvironment
{ baseState :: e -> s
, nextState :: e -> s -> a -> s
, reward :: forall r. (Num r) => e -> s -> a -> [r]
}
Instead of making an instance of the type class, you just make a value of the data type:
gameStateActionMAE :: MultiAgentEnvironment Game State Action
gameStateActionMAE = MultiAgentEnvironment
{ baseState = \game -> State{player=0, piles=initial_piles game}
, nextState = \game state action -> State{player=player state + 1 `mod` players game,
piles=zipWith (-) (piles state) (removed action)}
, reward = \game state action -> [0, 0]
}
One nice advantage of this method is that you can make multiple different MultiAgentEnvironments with the same types but that have different behaviors. Using them is pretty simple too: instead of having MultiAgentEnvironment e s a as a constraint, you now have it as just a regular old argument. In fact, if you turn on the RecordWildCards pragma, then any function that used to start with
foo :: MultiAgentEnvironment e s a => x -> y
foo x = ...
can now be written as
foo :: MultiAgentEnvironment e s a -> x -> y
foo mae#MultiAgentEnvironment{..} x = ...
and the body should be pretty much identical (well, unless the body calls a subfunction which requires the MultiAgentEnvironment, in which case you'll need to manually pass mae along).

Related

How to change the behavior of the function based on class constraints in Haskell?

I have a data type that represents a collection of values paired with a probability. At first, the implementation was just to use good old lists, but as you can imagine, this can be inefficient (for example, I use a Tree instead of a list to store ordered values)
After some research, I thought about using GADTs
data Tree a b = Leaf | Node {left::Tree a b, val :: (a, b), right :: Tree a b}
data Prob a where
POrd ::Ord a => Tree a Rational -> Prob a
PEq ::Eq a => [(a, Rational)] -> Prob a
PPlain ::[(a, Rational)] -> Prob a
So far, so good. I'm now stuck at trying to create a smart constructor for my new data type,
that takes [(a,Rational)] and depending on the constraints of a, chooses the correct constructor for Prob. Basically:
prob :: [(a, Rational)] -> Prob a
-- chooses the "best" constructor based on the constraints of a
Is this at all possible? If not, how should I go about designing something better? Am I missing something?
Thanks!
There is no way to perform a check of the form "is type T in class C?" in Haskell. The issue here is that it is hard to answer negatively to such question and allow separate compilation: T could be in C in the scope of one module but not in the scope of another one, causing a rather fragile semantics.
To ensure consistency, Haskell only allows to require a constraint, and raise an compile time error otherwise.
As far as I can see, the best you can do is to use another custom type class, which tells you which case is the best one. E.g.
{-# LANGUAGE AllowAmbiguousTypes, TypeApplications, ScopedTypeVariables #-}
data BestConstraint a where
BCOrd :: Ord a => BestConstraint a
BCEq :: Eq a => BestConstraint a
BCNone :: BestConstraint a
class BC a where
bestC :: BestConstraint a
instance BC Int where bestC = BCOrd
-- ... etc.
instance BC a => BC [a] where
bestC = case bestC #a of
BCOrd -> BCOrd
BCEq -> BCEq
BCNone -> BCNone
prob :: forall a . BestConstraint a => [(a, Rational)] -> Prob a
prob xs = case bestC #a of
BCOrd -> POrd .... -- build the tree
BCEq -> PEq xs
BCNone -> PPlain xs
You will have to provide an instance for any type you want to use, though.

How to convert Dynamic to Forall something

I have a cache with Dynamic values. Some of them have the type Delayed a.
Normally when I access the cache, I know the type a, so it's not a problem, I can use fromDynamic to cast to Maybe a.
I would like to call a function which doesn't need to know anything about the type a on a list of Dynamic. (The method is cancel :: Delay a -> IO ()).
Is there a way to do so ?
Basically I need a way to do get from Dynamic to Forall a . Delayed a ?
Edit
For information, Delayed holds a pending asynchronous value and a MVar to start or Cancel it. It is equivalent to
data Delayed m a = Delayed { blocker :: MVar Bool, async :: Async m a }
Such values are stored in a cache (which use Dynamic and store other things). When displaying the cache status, I need to be able to get the status of Delayed value (which involve accessing the blocker but has nothing to do with the actual value.
A value of type forall a . X a is a value which can be instantiated to any of X Int, X Bool, X String, etc. Presumably, your cache stores values of many different types, but no single value is valid at every possible type parameter. What you actually need is a value of type exists a . Delayed a. However, Haskell doesn't have first-class existential quantifiers, so you must encode that type in some way. One particular encoding is:
castToDelayed :: (forall a . Typeable a => Delayed a -> r) -> Dynamic -> r
Assume that you have this function; then you can simply write castToDelayed cancel :: Dynamic -> IO (). Note that the function parameter to castToDelayed provides a Typeable constraint, but you can freely ignore that constraint (which is what cancel is doing). Also note this function must be partial due to its type alone (clearly not every Dynamic is a Delayed a for some a), so in real code, you should produce e.g. Maybe r instead. Here I will elide this detail and just throw an error.
How you actually write this function will depend on which version of GHC you are using (the most recent, 8.2, or some older version). On 8.2, this is a very nice, simple function:
{-# LANGUAGE ViewPatterns #-}
-- NB: probably requires some other extensions
import Data.Dynamic
import Type.Reflection
castToDelayed :: (forall a . Typeable a => Delayed a -> r) -> Dynamic -> r
castToDelayed k (Dynamic (App (eqTypeRep (typeRep :: TypeRep Delayed) -> Just HRefl) a) x)
= withTypeable a (k x)
castToDelayed _ _ = error "Not a Delayed"
(Aside: at first I thought the Con pattern synonym would be useful here, but on deeper inspection it seems entirely useless. You must use eqTypeRep instead.)
Briefly, this function works as follows:
It pattern matches on the Dynamic value to obtain the actual value (of some existentially quantified type a) stored within, and the representation of its type (of type TypeRep a).
It pattern matches on the TypeRep a to determine if it is an application (using App). Clearly, Delayed a is the application of a type constructor, so that is the first thing we must check.
It compares the type constructor (the first argument to App) to the TypeRep corresponding to Delayed (note you must have an instance Typeable Delayed for this). If that comparison is successful, it pattern matches on the proof (that is Just HRefl) that the first argument to App and Delayed are in fact the same type.
At this point, the compiler knows that a ~ Delayed x for some x. So, you can call the function forall a . Typeable a => Delayed a -> r on the value x :: a. It must also provide the proof that x is Typeable, which is given precisely by a value of type TypeRep x - withTypeable reifies this value-level proof as a type-level constraint (alternatively, you could have the input function take as argument TypeRep a, or just omit the constrain altogether, since your specific use case doesn't need it; but this type is the most general possible).
On older versions, the principle is basically the same. However, TypeRep did not take a type parameter then; you can pattern match on it to discover if it is the TypeRep corresponding to Delayed, but you cannot prove to the compiler that the value stored inside the Dynamic has type Delayed x for some x. It will therefore require unsafeCoerce, at the step where you are applying the function k to the value x. Furthermore, there is no withTypeable before GHC 8.2, so you will have to write the function with type (forall a . Delayed a -> r) -> Dynamic -> r instead (which, fortunately, is enough for your use case); or implement such a function yourself (see the source of the function to see how; the implementation on older versions of GHC will be similar, but will have type TypeRep -> (forall a . Typeable a => Proxy a -> r) -> r instead).
Here is how you implement this in GHC < 8.2 (tested on 8.0.2). It is a horrible hack, and I make no claim it will correctly in all circumstances.
{-# LANGUAGE DeriveDataTypeable, MagicHash, ScopedTypeVariables, PolyKinds, ViewPatterns #-}
import Data.Dynamic
import Data.Typeable
import Unsafe.Coerce
import GHC.Prim (Proxy#)
import Data.Proxy
-- This part reifies a `Typeable' dictionary from a `TypeRep'.
-- This works because `Typeable' is a class with a single field, so
-- operationally `Typeable a => r' is the same as `(Proxy# a -> TypeRep) -> r'
newtype MagicTypeable r (kp :: KProxy k) =
MagicTypeable (forall (a :: k) . Typeable a => Proxy a -> r)
withTypeRep :: MagicTypeable r (kp :: KProxy k)
-> forall a . TypeRep -> Proxy a -> r
withTypeRep d t = unsafeCoerce d ((\_ -> t) :: Proxy# a -> TypeRep)
withTypeable :: forall r . TypeRep -> (forall (a :: k) . Typeable a => Proxy a -> r) -> r
withTypeable t k = withTypeRep (MagicTypeable k) t Proxy
-- The type constructor for Delayed
delayed_tycon = fst $ splitTyConApp $ typeRep (Proxy :: Proxy Delayed)
-- This is needed because Dynamic doesn't export its constructor, and
-- we need to pattern match on it.
data DYNAMIC = Dynamic TypeRep Any
unsafeViewDynamic :: Dynamic -> DYNAMIC
unsafeViewDynamic = unsafeCoerce
-- The actual implementation, much the same as the one on GHC 8.2, but more
-- 'unsafe' things
castToDelayed :: (forall a . Typeable a => Delayed a -> r) -> Dynamic -> r
castToDelayed k (unsafeViewDynamic -> Dynamic t x) =
case splitTyConApp t of
(((== delayed_tycon) -> True), [a]) ->
withTypeable a $ \(_ :: Proxy (a :: *)) -> k (unsafeCoerce x :: Delayed a)
_ -> error "Not a Delayed"
I don't know what Delayed actually is, but lets assume it's defined as follows for testing purposes:
data Delayed a = Some a | None deriving (Typeable, Show)
Then consider this simple test case:
test0 :: Typeable a => Delayed a -> String
test0 (Some x) = maybe "not a String" id $ cast x
test0 None = "None"
test0' =
let c = castToDelayed test0 in
[ c (toDyn (None :: Delayed Int))
, c (toDyn (Some 'a'))
, c (toDyn (Some "a")) ]
Why not define
{-# LANGUAGE ExistentialQuantification #-}
data Delayed' = forall a. Delayed' (Delayed a)
and then store than in the Dynamic? You can then cast it out of the dynamic, case on it, and pass the result to cancel. (Depending on what your use case is you may no longer even need the Dynamic.)

How can I encode and enforce legal FSM state transitions with a type system?

Suppose I have a type Thing with a state property A | B | C,
and legal state transitions are A->B, A->C, C->A.
I could write:
transitionToA :: Thing -> Maybe Thing
which would return Nothing if Thing was in a state which cannot transition to A.
But I'd like to define my type, and the transition functions in such a way that transitions can only be called on appropriate types.
An option is to create separate types AThing BThing CThing but that doesn't seem maintainable in complex cases.
Another approach is to encode each state as it's own type:
data A = A Thing
data B = B Thing
data C = C Thing
and
transitionCToA :: C Thing -> A Thing
This seems cleaner to me. But it occurred to me that A,B,C are then functors where all of Things functions could be mapped except the transition functions.
With typeclasses I could create somthing like:
class ToA t where
toA :: t -> A Thing
Which seems cleaner still.
Are there other preferred approaches that would work in Haskell and PureScript?
Here's a fairly simple way that uses a (potentially phantom) type parameter to track which state a Thing is in:
{-# LANGUAGE DataKinds, KindSignatures #-}
-- note: not exporting the constructors of Thing
module Thing (Thing, transAB, transAC, transCA) where
data State = A | B | C
data Thing (s :: State) = {- elided; can even be a data family instead -}
transAB :: Thing A -> Thing B
transAC :: Thing A -> Thing C
transCA :: Thing C -> Thing A
transAB = {- elided -}
transAC = {- elided -}
transCA = {- elided -}
You could use a type class (available in PureScript) along with phantom types as John suggested, but using the type class as a final encoding of the type of paths:
data A -- States at the type level
data B
data C
class Path p where
ab :: p A B -- One-step paths
ac :: p A C
ca :: p C A
trans :: forall a b c. p c b -> p b a -> p c a -- Joining paths
refl :: forall a. p a a
Now you can create a type of valid paths:
type ValidPath a b = forall p. (Path p) => p a b
roundTrip :: ValidPath A A
roundTrip = trans ca ac
Paths can only be constructed by using the one-step paths you provide.
You can write instances to use your paths, but importantly, any instance has to respect the valid transitions at the type level.
For example, here is an interpretation which calculates lengths of paths:
newtype Length = Length Int
instance pathLength :: Path Length where
ab = Length 1
ac = Length 1
ca = Length 1
trans (Length n) (Length m) = Length (n + m)
refl = Length 0
Since your goal is to prevent developers from performing illegal transitions, you may want to look into phantom types. Phantom types allow you to model type-safe transitions without leveraging more advanced features of the type system; as such they are portable to many languages.
Here's a PureScript encoding of your above problem:
foreign import data A :: *
foreign import data B :: *
foreign import data C :: *
data Thing a = Thing
transitionToA :: Thing C -> Thing A
Phantom types work well to model valid state transitions when you have the property that two different states cannot transition to the same state (unless all states can transition to that state). You can workaround this limitation by using type classes (class CanTransitionToA a where trans :: Thing a -> Thing A), but at this point, you should investigate other approaches.
If you want to store a list of transitions so that you can process it later, you can do something like this:
{-# LANGUAGE DataKinds, GADTs, KindSignatures, PolyKinds #-}
data State = A | B | C
data Edge (a :: State) (b :: State) where
EdgeAB :: Edge A B
EdgeAC :: Edge A C
EdgeCA :: Edge C A
data Domino (f :: k -> k -> *) (a :: k) (b :: k) where
I :: Domino f a a
(:>>:) :: f a b -> Domino f b c -> Domino f a c
infixr :>>:
example :: Domino Edge A B
example = EdgeAC :>>: EdgeCA :>>: EdgeAB :>>: I
You can turn that into an instance of Path by writing a concatenation function for Domino:
{-# LANGUAGE FlexibleInstances #-}
instance Path (Domino Edge) where
ab = EdgeAB :>>: I
ac = EdgeAC :>>: I
ca = EdgeCA :>>: I
refl = I
trans I es' = es'
trans (e :>>: es) es' = e :>>: (es `trans` es')
In fact, this makes me wonder if Hackage already has a package that defines "indexed monoids":
class IMonoid (m :: k -> k -> *) where
imempty :: m a a
imappend :: m a b -> m b c -> m a c
instance IMonoid (Domino e) where
imempty = I
imappend I es' = es'
imappend (e :>>: es) es' = e :>>: (es `imappend` es')

Haskell Typeclass Instance based on canonical view

As a self assigned exercise of sorts, I'm playing around with implementing an algebra based numeric type heirarchy.
I'd like to specify that if a structure can be viewed in a canonical way as something that satisfies one of my typeclasses, then it should be an instance of that typeclass as well. To that end I've tried essentially the following:
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
FlexibleContexts, FlexibleInstances #-}
class AbGp s a where
plus :: a -> a -> s -> a
zero :: s -> a
minus :: a -> a -> s -> a
class View a b c | a c -> b
view :: a -> b
instance (View s s1 a, AbGp s1 a) => AbGp s a
plus x y s = plus x y (view s)
zero = zero . view
minus x y s = minus x y (view s)
s should be thought of as holding the definitions of the operations in the group, and a as the type of the elements in the group.
But this doesn't work, which isn't surprising, but what I want to do now is:
Suppose I know that some type s, say s that represents a Ring, can be mapped canonically to s1 which is a datastructure I already have an instance for as an AbGp, then I would like s to also be automatically an instance of AbGp. How can I do this?
I'm thinking of doing the following, if it'll work, but I'd like to know if there is a better way:
instance (AbGp s1 a) => AbGp (s1,b) a where
-- ...

How to avoid ugly code resolving this problem in Haskell (LANGUAGE extentions)?

I'm trying to write a program that simulates several creatures in a world. Basically the word sends a message over a list of creatures, and each creature gives his response, which in turn modifies the world.
I simplified what I'm trying to write in the following skeleton:
module Structure0 where
type Message = String
class Creature a where
processInput :: a -> Message -> Message
class World a where
processAction :: a -> b -> Message -> a
getCreatures :: a -> [b]
---- USAGE EXAMPLE ----
data Parrot = Parrot Int deriving Show
instance Creature Parrot where
processInput p s = s
data ParrotWorld = ParrotWorld [Parrot]
instance World ParrotWorld where
processAction w p s = w
getCreatures (ParrotWorld ps) = ps
In this code, I would that the parameter b in World class definition could assume all the data value that belong to the Creature class, something like:
processAction :: (Creature b) => a -> b -> Message -> a
Of course this examples aren't actual haskell code, lo let's pass illustrating two solution i found: the first, involving ExistentialQuantification:
{-# LANGUAGE ExistentialQuantification #-}
module Structure1 where
type Message = String
class Creature_ a where
processInput :: a -> Message -> Message
data Creature = forall c. Creature_ c => Creature c
instance Creature_ Creature where
processInput (Creature c) = processInput c
class World a where
processAction :: a -> Creature -> Message -> a
getCreatures :: a -> [Creature]
---- USAGE EXAMPLE ----
data Parrot = Parrot Int deriving Show
instance Creature_ Parrot where
processInput u s = s
data ParrotWorld = ParrotWorld [Creature]
instance World ParrotWorld where
processAction w p s = w
getCreatures (ParrotWorld ps) = ps
and the second, suggested by a kind guy on #haskell, using TypeFamilies:
{-# LANGUAGE TypeFamilies, FlexibleContexts #-}
module Structure2 where
type Message = String
class Creature a where
processInput :: a -> Message -> Message
class (Creature (WorldCreature a)) => World a where
type WorldCreature a :: *
processAction :: a -> WorldCreature a -> Message -> a
getCreatures :: a -> [WorldCreature a]
---- USAGE EXAMPLE ----
data Parrot = Parrot Int deriving Show
instance Creature Parrot where
processInput p s = s
data ParrotWorld = ParrotWorld [Parrot]
instance World ParrotWorld where
type WorldCreature ParrotWorld = Parrot
processAction w p s = w
getCreatures (ParrotWorld ps) = ps
The main objective of this exercise is writing nice, elegant code.
So, the questions:
1) Should I express Creature as a Class instead of a Data?
(I'm doing this because a Creature is just a thing that implement the processInput function, and the many actual Creature implementations vary a lot; expecially during prototyping, I'd like not to change constantly the way in which a Creature pattern-matches.
2) The first solution I provide it's a bit ugly due to the boilerplate of maintaing both Creature and Creature_ versions. It has the benefit, however, that I can write mixed list of type [Creature]; Problem is that I can't pattern match against an object, id est things like:
\(Creature (Parrot x)) -> x
will fail due to type system. Can I make this all right?
3) The second solution has a problem of extendibility: say I would to construct a World with two types of creatures, say Parrot1 and Parrot2: how could I write the code in that case?
4) Am I structuring the code from a wrong point of view? Can I get an elegant solution just using plain haskell?
Thank you all :)
Carlo
1 class vs. data
Creature should be a class -- it describes an interface. Data should be used when you think of actually communicating values, or when you need to introduce a new type, wrapping an existing object with new behavior. For example, the Identity monad needs to wrap its values in a new type, or else you'd see instance Monad a for all a, which would cause conflicts with making anything else a Monad instance. But, you may need to wrap it.
2 lists
There is a way to do it with Data.Dynamic, but every time I've thought about doing it that way, I've been able to think of a way to do it with regular typeclasses instead. That said, I haven't written that much Haskell, and many libraries certainly rely on Data.Dynamic. If you want to really unbox a type, then you probably need to use it.
3 extensionality
As before, if you can leave type-specific functionality in the classes, that is best. It'd be most helpful if you could post an example, showing why you can't add another function to Creature. I'll assume you want to count numParrots in the example below, and you really do need to unbox them.
4 general comments
There are always many solutions to a problem. Based on your description, I'd think that "different worlds should entail different types of messages", not that a world should be tied to a specific type of creature (e.g. ParrotWorld).
another solution
here's my solution, using Data.Typeable. As mentioned above, it's my first time using it, so there may be a cleaner way.
{-# LANGUAGE DeriveDataTypeable,
ImpredicativeTypes,
NoMonomorphismRestriction,
RankNTypes,
ScopedTypeVariables #-}
module Test where
import Data.Typeable
type Message = String
class Typeable α => Creature α where
processInput :: α -> Message -> Message
-- box a creature
type BoxedC = (Message -> Message, Typeable β => Maybe β)
boxC :: Creature α => α -> BoxedC
boxC x = (processInput x, cast x)
class World α where
-- from your description, I'd not have Creature as part of this.
processAction :: α -> Message -> α
getCreatures :: α -> [BoxedC]
data Parrot = Parrot { parrotMessage :: String } deriving Typeable
data Lizard = Lizard { lizardMessage :: String } deriving Typeable
instance Creature Parrot where processInput p _ = (parrotMessage p)
instance Creature Lizard where processInput l _ = (lizardMessage l)
-- NOTE: Keep it simple and use a single World instance
-- (i.e. no typeclass) unless you need it.
data BaseWorld = BaseWorld { creatureList :: [BoxedC] }
instance World BaseWorld where
processAction w _ = w
getCreatures = creatureList
w = BaseWorld [boxC $ Parrot "parrot1", boxC $ Lizard "Lizard1"]
numParrots :: [BoxedC] -> Int
numParrots lst = foldl (+) 0 (map (go . snd) lst) where
go :: (forall β. Typeable β => Maybe β) -> Int
go (Just x :: Maybe Parrot) = 1
go _ = 0
test = numParrots (getCreatures w)
The idea is similar to yours: we box creatures before we put them in a list. The boxed elements have enough data so that you can unbox the type if you need to. One final thing to mention, though it's maybe not what you want here, is that closures are powerful. You don't need to keep a list of creatures if you can express their results as function composition. For example, in pseudocode, you could have a function
bind_creature :: Creature -> World -> World
which adds a creature to a world, and World has a type which returns its next iteration,
data World = World { nextWorld :: World }
which you set to itself for the base, namely w = World w. For simplicity, let's assume that each creature has a function
transformWorld :: Creature -> World -> World
then you could implement bind_creature like,
bind_creature c w = World { nextWorld = transformWorld c (nextWorld w) }
hope it helps.

Resources