Question

I am working on a library to study game theoretic learning. In this setting, N agents are brought together and interact with an environment. Each agent derives a model of the interaction. The model of one agent depends on its N-1 opponents. I wrote the code determining that model for 1 agent and 2 agents, and am trying to generalize it. Here is part of the code I have:

data System w x a s h h' = System { signaling :: SignalingWXAS w x a s
                                  , dynamic   :: DynamicXAS x a s
                                  , strategy  :: MockupStrategy x a s h h' }

data JointState w x a s h h' = JointState { worldState  :: w
                                          , state       :: x
                                          , mockupState :: MockupState a s h h' }

systemToMockup :: ( Bounded w, Ix w, Bounded x, Ix x
                  , Bounded a, Ix a, Bounded s, Ix s
                  , Bounded (h a), Ix (h a), Bounded (h' s), Ix (h' s)
                  , History h, History h'
                  ) => System w x a s h h' -> Mockup a s h h'
systemToMockup syst = mock
    where
      mock z   = norm $ statDist >>=? condit z >>= computeStatesAndAction >>= sig >>=$ extractSignal
      statDist = ergodicStationary $ transition syst
      condit z = just z . mockupState
      sig      = uncurryN $ signaling syst
      strat    = strategy syst
      computeStatesAndAction joint = do
        let w = worldState joint
        let x = state joint
        a <- strat x (mockupState joint)
        return (w, x, a)
      extractSignal (_, s) = s

and

data System2 w x1 a1 s1 h1 h1' x2 a2 s2 h2 h2' = System2 { signaling :: SignalingWXAS2 w x1 a1 s1 x2 a2 s2
                                                         , dynamic1  :: DynamicXAS x1 a1 s1
                                                         , dynamic2  :: DynamicXAS x2 a2 s2
                                                         , strategy1 :: MockupStrategy x1 a1 s1 h1 h1'
                                                         , strategy2 :: MockupStrategy x2 a2 s2 h2 h2' }

data JointState2 w x1 a1 s1 h1 h1' x2 a2 s2 h2 h2' = JointState2 { worldState   :: w
                                                                 , state1       :: x1
                                                                 , mockupState1 :: MockupState a1 s1 h1 h1'
                                                                 , state2       :: x2
                                                                 , mockupState2 :: MockupState a2 s2 h2 h2' }
systemToMockups2 syst = (mock1, mock2)
    where
      mock1 z1   = norm $ statDist >>=? condit1 z1 >>= computeStatesAndActions >>= sig >>=$ extractSignal1
      mock2 z2   = norm $ statDist >>=? condit2 z2 >>= computeStatesAndActions >>= sig >>=$ extractSignal2
      statDist   = ergodicStationary $ transition2 syst
      condit1 z1 = just z1 . mockupState1
      condit2 z2 = just z2 . mockupState2
      sig        = uncurryN $ signaling syst
      strat1     = strategy1 syst
      strat2     = strategy2 syst
      computeStatesAndActions joint = do
        let w  = worldState joint
        let x1 = state1 joint
        let x2 = state2 joint
        a1 <- strat1 x1 (mockupState1 joint)
        a2 <- strat2 x2 (mockupState2 joint)
        return (w, x1, a1, x2, a2)
      extractSignal1 (_, s, _) = s
      extractSignal2 (_, _, s) = s

I am after a function definition for systemToMockupN that could accommodate any finite number of agents.

Agents are heterogenous so use of lists is not directly possible. I cannot use tuples because I do not know the size in advance. I tried using curryN, uncurryN, etc. but did not manage to do one operation on every element of a tuple. I tried building a variadic function in a fashion similar to printf with no success.

I know I could use template haskell but I am wondering if there is a nicer solution I am overlooking. Any pointer to some code out there dealing with a finite but arbitrary number of heterogenous elements would be greatly appreciated.

Was it helpful?

Solution

Generalised Algebraic Data Types, (GADT).

These let you bring finitely many genuinely heterogenous data types together into one, and are the modern way to do existential types. They sit somewhere in between the data Agent = AH Human | AP Plant | .... approach and the HList approach. You can make all your incredibly heterogenous agents instances of some typeclass, then bundle them together in the AgentGADT. Make sure your typeclass has everything you'll ever want to do to an Agent in it, because it's hard to get data back out of a GADT without a function with an explicit type; will you need getHumans [AgentGADT] -> [Human]? or updateHumans :: (Human->Human) -> [AgentGADT] -> [AgentGADT]? That'd be easier with the ordinary abstract data type in my other post.

Plus points: You can have [AgentGADT] and operate uniformly using class functions, whilst writing weird and wonderfully parameterised data types. Minus points - hard to get your Agent data out once it's in.

My favourite introductory text online was GADTs for dummies.

OTHER TIPS

Heterogenous. I don't think you should do this, but you did ask.

You can use en existing library for heterogenous lists, eg HList. This secretly uses Template Haskell anyway, but you don't need to get your hands as dirty as if you did it yourself.

Languages with dynamic typing have all sorts of problems because of the need for casting etc. HList is type-safe, but it's still not easy in my view to write code that works well and isn't buggy. You get an edge over tuples because you don't need to change type, and mapping your updates across elements should be easier, but it's still not pretty.

Don't go heterogenous. It's not worth it. It is worth finding a better way. Here's one approach to avoiding it. (There are other paths.) There might be an arbitrary number of agents, but surely there aren't an arbitrary number of types of agents. (Do the types really need to be so parameterised? Your generality is costing you too much I fear.

    class AnAgent a where 
         liveABit :: World -> a -> (World,a)
         ...
         ...

    data NuclearPlant = ....
    data CoalPlant = ....
    data WidFarm = .....

    data DataCenter = .....

    data EnvFriendly = .....
    data PetrolHead = .....

Group them together a bit for common treatment via pattern matching if it's convenient:

    data Plant = PN NuclearPlant | PC CoalPlant | PW WindFarm
    data Human = HEF EnvFriendly | HPE PetrolHead

    data Agent = AP Plant | AH Human | AD DataCenter

Common/heterogenous treatment within groups/accross groups:

    bump :: Agent -> Agent
    bump (Human h) = Human (breakleg h)
    bump a = a

You can then define all the agents you want then pop them in a [Agent] and define a nice eachLiveABit :: World -> [Agent] -> (World,[Agent]) to update the world and its agents. You can make AnAgent instances of individual agent types or groups, and build up to Agent, (or maybe even do without the type class even and just use ordinary functions).

This would follow the (Classes + Interesting Type System Features) -> (Types and Higher Order Functions) program transformation that feels emotionally like your dumbing down a bit, but makes much of the trouble go.

You could try to solve that using type classes.
Here is some pseudo code:

data Mockup = Mockup1 <return type of systemToMockup>
            | Mockup2 <return type of systemToMockups2>

class SystemToMockup a where
    systemToMockup :: a -> Mockup

instance SystemToMockup (System1 ...) where
    <implementation of systemToMockup>

instance SystemToMockup (System2 ...) where
    <implementation of systemToMockups2>

This is a rather limited solution and I doubt it'll work for you since your application seems to be quite complex.
In general the approach of C. A. McCann is much better.

Update: One thing this strategy cannot handle is polymorphic return types. Also, parameters that have different types depending on the main type add quite a bit of complexity.

It's been mentioned in the comments, but one of the best ways to do a "heterogeneous collection" is to decide what operations you can actually do on each element of the collection (since you'll only be able to do a restricted set of things on them, even if your language had duck typing) and store a record of those operations. Example:

data Thing1 = ...
data Thing2 = ...

data AThing = AThing {
  op1 :: ...
  op2 :: ...
}

class IsAThing a where
    mkAThing :: a -> AThing

instance IsAThing Thing1 where
    mkAThing a = AThing {
            op1 = op1_for_thing1 a,
            op2 = op2_for_thig1 a
        }

Then, to call op1 on any IsAThing:

op1 (mkAThing a) <...other args...>

Though, in your case you want a list of AThing:

[mkAThing a2, mkAThing a2, ...]

Then on any element:

op1 <element of that list> <...other args...>
Licensed under: CC-BY-SA with attribution
Not affiliated with StackOverflow
scroll top