[Haskell-beginners] A rigid type and a better pattern

Daniel Fischer daniel.is.fischer at web.de
Sun Aug 16 09:42:44 EDT 2009


Am Sonntag 16 August 2009 14:04:10 schrieb Javier M Mora:
> (I had problems sending this email and I don't know if earlier arrived
> to  mail list. I'm going to send again. Sorry if you get it duplicate)
>
>
>
> Hi All, this is my first email to beginners list. I'm ending my Master
> Degree in Robotics (in Spain). One of my assignment is about Motion
> Planning and I thought solve with Haskell. This is my problem:
>
> * Every robot has a local state. I can get the position of the robot
> from the state. The state can be rect coords or polar coords or distance
> moved on a fixed path or whatever.
>
> * I have a global state witch keep the local state of each robot.
>
> * Every state has a different system to action over it. So, in distance
> over fixed path we can "stop" or "go". In polar coords we can increase
> and decrease the radius and phi. And in rect coords we can move in x and
> y direction
>
> * I have several robots at same time. But every robot has the same state
> and the same action. So, all robots in the run of my program has same
> local state and action.
>
> So, I split the algorithm in a common part (used in all states and
> actions) and other for each specific state-action.
>
> This is the structure (abstract):
>      class Robot a where
>      ...
>
>      class State a where
>        getpos a -> [Position]
>      ...
>
>      class Action a where
>      ...
>
> later I have instances for concrete cases. In phase 1, local state is a
> Int for each robot and action is a Bool (stop or run).
>
>      data State1 = State1 [Int]
>      instance State State1 where
>        getpos (State1 a) = ...
>      ...
>
>      data Action1 = Action1 [Bool]
>      instance Action Action1 where
>      ...
>
>
> I have a function "newstate" to calculate the new state from an old
> state and the action. This is the type signature:
>
>      newstate:: (State a,Action b) => a -> b -> a
>
> and my instantiation in phase 1 is
>
>      newstate (State1 s) (Action1 u) = State1 $
>           zipWith (\x y -> if y then succ x else x) s u
>
> I want to use polymorphism in newstation because I need use
>     newstate (State2 s) (Action2 u)
> in the future (phase 2) so I tried include newstate in a typeclass.
>
> But if I write:
>
>   class State a where
>     newstate:: (Action b)=> a -> b -> a
>     ...
>
> or
>
>   class Action a where
>     newstate:: (State b) => b -> a -> b
>     ...
>
> (and move newstate definition to correct instance block)
>
> I get similar errors in both cases: (this is the first case):
>
>     Couldn't match expected type `b' against inferred type `Action1'
>       `b' is a rigid type variable bound by
>           the type signature for `newstate' at Tipos.hs:17:24
>     In the pattern: Action1 u
>     In the definition of `newstate':
>         newstate (State1 s) (Action1 u)
>                       = State1 $ zipWith (\ x y -> if y then succ x
> else x) s u
>     In the instance declaration for `State State1'
>

Yes. The above signatures promise that newstate will work given any pair of arguments 
whose types belong to classes State and action respectively, so in the definition you 
can't pattern match on constructors since you have to be polymorphic.

You can make it one multi-parameter type class

{-# LANGUAGE MultiParamTypeClasses #-}

class ActState a s where
    newstate :: s -> a -> s

instance ActState Action1 State1 where
    newstate (State1 s) (Action1 u) = ...

From the above I have the impression that each action type only works on one state type 
and each state type has only one action type that works for it, thus you could use 
functional dependencies or data families to aid resolution of instances. Since Robots are 
associated with States and Actions (presumably again in a 1-1 correspondence), it makes 
sense to tie them into it.

With functional dependencies:

{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}

class ActState a s | a -> s, s -> a where
    newstate :: s -> a -> s

instance ActState Action1 State1 where
    newstate (State1 s) (Action1 u) = ...

class (ActState a s) => Robot r s a | r -> s, r -> a, s -> r, s-> a, a -> r, a -> s where
    ...

instance Robot Robot1 State1 Action1 where
    ...

(or leave out the ActState class and have it all in class Robot)

With type Families:
{-# LANGUAGE MultiParamTypeClasses, TypeFamilies #-}

class Rob2 r where
    data St r
    data Ac r
    initstate :: St r
    newstate :: St r -> Ac r -> St r


instance Rob2 Robot1 where
    data St Robot1 = State2 [Int] deriving Show
    data Ac Robot1 = Action2 [Bool] deriving Show
    initstate2 = State2 [0,0,0]
    newstate2 (State2 xs) (Action2 gs) = 
                State2 $ zipWith (\x g -> if g then succ x else x) xs gs

or, moving the families outside the class:

data family St3 r
data family Ac3 r

data instance St3 Robot1 = State3 [Int] deriving Show
data instance Ac3 Robot1 = Action3 [Bool] deriving Show

class Rob3 r where
    initstate3 :: St3 r
    newstate3 :: St3 r -> Ac3 r -> St3 r

instance Rob3 Robot1 where
    initstate3 = State3 [0,0,0]
    newstate3 (State3 xs) (Action3 gs) = 
                State3 $ zipWith (\x g -> if g then succ x else x) xs gs

>
> My questions:
>
> * How can I fix this error?
>
> * the point is associate every instance of Robot with one instance of
> State and with one instance of Action. So when I select the Robot I'm
> goint to use I get "automagically" the correct instances of newstate and
> others.
>
> Is there a pattern to this behaviour?

Functional dependencies/Type families.
Or you could use parameterized types.

data Distance = Distance Double
data Polar = Polar Double Double
data Cartesian = Cartesian Int Int

data Action a = Action [a -> a]
data State a = State [a]
data Robot a = Robot ???

class Robot a where
    initstate :: State a
    newstate :: State a -> Action a -> State a

instance Robot Distance where ...
instance Robot Polar where ...
instance Robot Cartesian where ...

>
> My ideal is associate every function related with a Robot with a general
> typeclass "Robot" (I don't tested this) :
>
>   class Robot a where
>     initstate:: (State a) => a
>     newstate:: (State a,Action b) => a-> b-> a
>
> And the instance:
>
>   instance Robot Robot1 where
>     initstate = State1 [0,0,0]
>     newstate (State1 a) (Action1 b) = ...
>
> and
>
>   instance Robot Robot2 where
>     initstate = State2 [(0,0),(1,1),(2,2)] -- i.e.
>     newstate (State2 a) (Action2 b) = ...
>
> and so on.
>
> But I think It can't work because neither initstate or newstate use Robot1.
>
> Any tips?
>
>
>
>
>
> Javier M Mora.



More information about the Beginners mailing list