[Haskell-cafe] Re: Fwd: Re: Simple game: a monad for each player

2010-05-01 Thread Heinrich Apfelmus
Limestraël wrote:
 Heinrich, I saw you updated your operational package (you considered my
 remark about ProgramView, thank you)

Your feedback is much appreciated. :)

 I saw you added a liftProgram function, however it is not like the mapMonad
 function you were talking about.
 mapMonad was:
 mapMonad :: (Monad m1, Monad m2) =
 (forall a . m1 a - m2 a)
- ProgramT instr m1 a
- ProgramT instr m2 a
 
 and you turned it into the less generic:
 liftProgram :: Monad m = Program instr a - ProgramT instr m a
 
 Did you change your mind?

Yes, I opted for the less generic function. My reasons were:

a)  mapMonad  has a precondition that is not caught by the type checker.
Namely, the first argument  f :: forall a. m1 a - m2 a  must respect
the monad laws, i.e.

f . return  = return
f (m = k) = f m = f . k

If the  f  supplied by the user doesn't satisfy these equations, then it
will break invariants internal to the library, which is bad.

b) Excluding  mapMonad  does not go beyond the  mtl  in that the latter
does not provide functions

mapStateT :: (Monad m1, Monad m2) =
  = (forall a . m1 a - m2 a)
  - StateT s m1 a - StateT s m2 a

either.

b') The TicTacToe example only uses  m = IO  and  m = Identity  and
liftProgram  is enough for that.

Basically, I'm unsure about the whole business of monad modularity. No
completely satisfactory solution has emerged yet, so I'm copying the
mtl  style for now.

c) Fortunately, users of the library don't lose functionality, only
convenience, because they can implement  mapMonad  themselves if they so
desire:

mapMonad f = id' = lift . f . viewT
where
id' :: ProgramViewT instr m1 a - ProgramT instr m2 a
id' (Return a) = return a
id' (i := k) = singleton i = mapMonad f . k

(This is contrary to what I said earlier,  mapMonad  does *not* have to
be a library function.)


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Fwd: Re: Simple game: a monad for each player

2010-04-19 Thread Heinrich Apfelmus
Heinrich Apfelmus wrote:
 Limestraël wrote:
 Okay, I start to understand better...

 Just, Heinrich, how would implement the mapMonad function in terms of the
 operational package?
 You just shown the signature.
 
 Ah, that has to be implemented by the library, the user cannot implement
 this. Internally, the code would be as Bertram suggests:
 
 mapMonad :: (Monad m1, Monad m2)
  = (forall a . m1 a - m2 a)
  - ProgramT instr m1 a - ProgramT instr m2 a
 mapMonad f (Lift m1)  = Lift (f m1)
 mapMonad f (Bind m k) = Bind (mapMonad f m) (mapMonad f . k)
 mapMonad f (Instr i)  = Instr i

Silly me! This can be implement by the user:

mapMonad f = id' = lift . f . viewT
where
id' :: ProgramViewT instr m1 a - ProgramT instr m2 a
id' (Return a) = return a
id' (i := k) = singleton i = mapMonad f . k

and it would be a shame for the operational approach if that were not
possible. :)


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Fwd: Re: Simple game: a monad for each player

2010-04-15 Thread Heinrich Apfelmus
Limestraël wrote:
 Okay, I start to understand better...
 
 Just, Heinrich, how would implement the mapMonad function in terms of the
 operational package?
 You just shown the signature.

Ah, that has to be implemented by the library, the user cannot implement
this. Internally, the code would be as Bertram suggests:

mapMonad :: (Monad m1, Monad m2)
 = (forall a . m1 a - m2 a)
 - ProgramT instr m1 a - ProgramT instr m2 a
mapMonad f (Lift m1)  = Lift (f m1)
mapMonad f (Bind m k) = Bind (mapMonad f m) (mapMonad f . k)
mapMonad f (Instr i)  = Instr i

I was musing that every instance of  MonadTrans  should implement this
function.

Also note that there's a precondition on  f  , namely it has to respect
the monad laws:

f (m = k) = f m = f . k
f return= return

For instance,

f :: Identity a - IO a
f x = launchMissiles  return (runIdentity x)

violates this condition.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Fwd: Re: Simple game: a monad for each player

2010-04-15 Thread Limestraël
Ok, but there is no function such as mapMonad in the operational package?

By the way, I noticed that ProgramT is not automatically made instance of
MonadIO when possible. It could be:
instance (MonadIO m) = MonadIO (ProgramT r m) where
liftIO = lift . liftIO

Is that intentional?
( In fact, I think it's a slip in the mtl package itself, since every
instance of MonadTrans can be declared instance of MonadIO:
instance (MonadTrans t, MonadIO m) = MonadIO (t m) where
liftIO = lift . liftIO
)

By the way, I finally managed to use operational to modify my TicTacToe
game.
(One shot, by the way, I had no bugs ^^. Very nice when it happens...)
Human player and AI are working. I'm currently fixing the Network player.
If you are interested, I could upload my code (it can be another example of
how to use the operational package).

In the end, I used a mix of your solution and my former one.
I have a Request datatype:
data Request a where
  GetGrid   :: Request Grid
  TurnDone  :: (Grid, Maybe GridResult) - Request ()
  GetResult :: Request (Maybe GridResult)

(Grid is what you called Board, GridResult is a type which indicates if
someone wins or if there is a draw)

The game monad is PlayerMonadT, and is a newtype:

newtype PlayerMonadT m a = PMT (ProgramT Request m a)
  deriving (Functor, Monad, MonadTrans)

I still have a datatype Player, which contains functions: (I tried to use
classes, but it was more complicated)

data Player m m' = Player {
  -- | Gets the mark (Cross or Circle) of the player
  plMark  :: Mark,
  -- | Called when the player must play
  plTurn  :: Grid - m Pos,
  -- | Called when player tries to play at a forbidden position
  plForbidden :: Pos - m (),
  -- | Called when game has ended.
  plGameOver  :: GridResult - m (),
  -- | Used to reach PlayerMonad in the monad stack
  plLift  :: forall a. PlayerMonadT m' a - m a,
  -- | Used to run the monad stack the player runs in
  plRun   :: forall a. m a - PlayerMonadT m' a
}

*m* is the monad stack the player runs in. It must be able to run it, by
providing a plRun function.
*m'* is the top monad, which can't be run (IO for human, any monad for AI,
etc.)
The alteration done to this type is the addition of the plLift and plRun
functions. Those are the functions you, Heinrich, and Bertram told me about.

Then, *all* the players play according to this logic:

playerLogic :: (Monad m) = Player m m' - m ()
playerLogic pl = do
  let toProg = plLift pl . PMT . singleton
  grid - toProg GetGrid
  pos - plTurn pl grid
  case checkCell grid (plMark pl) pos of
Nothing - do-- The cell was already filled in
  plForbidden pl pos -- We signal the error
  playerLogic pl -- We start the turn again
Just newGridAndResult - do
 -- The cell has been successfully marked, so we got
a new grid
  toProg $ TurnDone newGridAndResult
 -- At this point, the interpreter will switch to
the other player
  mbResult - toProg $ GetResult
 -- This player is back, and wants to know what's
new
  case mbResult of
Nothing  - playerLogic pl
Just res - plGameOver pl res

We can then run this function with the player custom stack thanks to the
runPlayer function:
runPlayer :: (Monad m) = Player m m' - PlayerMonadT m' ()
runPlayer pl = plRun pl $ playerLogic pl

And finally, the interpreter:
doGame :: (Monad m) = Grid - [PlayerMonadT m ()] - m Grid
doGame initGrid players =
  mapM unwrap players = flip evalStateT (initGrid, Nothing) . eval
  where
unwrap (PMT pl) = viewT pl

eval :: (Monad m) = [PromptT Request m ()] - StateT (Grid, Maybe
GridResult) m Grid

eval [] = liftM fst get

eval ((Return _) : pls) = eval pls

eval ((GetGrid := pl) : pls) = do
  (grid, _) - get
  p - lift . viewT $ pl grid
  eval $ p : pls

eval ((TurnDone (newGrid, mbResult) := pl) : pls) = do
  put (newGrid, mbResult)
  p - lift . viewT $ pl ()
  eval $ pls ++ [p]

eval ((GetResult := pl) : pls) = do
  (_, mbResult) - get
  p - lift . viewT $ pl mbResult
  eval $ p : pls

The game can be launched by doing for example:
let pl1 = humanPlayer Cross
let pl2 = artificialPlayer Circle levelOfDifficulty
doGame blankGrid [runPlayer pl1, runPlayer pl2]

I did it!

2010/4/15 Heinrich Apfelmus apfel...@quantentunnel.de

 Limestraël wrote:
  Okay, I start to understand better...
 
  Just, Heinrich, how would implement the mapMonad function in terms of the
  operational package?
  You just shown the signature.

 Ah, that has to be implemented by the library, the user cannot implement
 this. Internally, the code would be as Bertram suggests:

mapMonad :: (Monad m1, Monad m2)
 = (forall a . m1 a - m2 a)
 - ProgramT instr m1 a - ProgramT instr m2 a
mapMonad f (Lift m1)  = Lift (f m1)
mapMonad f (Bind m k) = Bind (mapMonad f m) (mapMonad f . k)
mapMonad f (Instr i)  = Instr i

 I 

Re: [Haskell-cafe] Re: Fwd: Re: Simple game: a monad for each player

2010-04-15 Thread Limestraël
There is the project.

I changed some little things with the player datatype. For flexibility sake,
it's stack has no longer to contain PlayerMonadT (I needed it for the net
player client)

The most interesting part (the one that deals with operational) is in
TicTacToe/Game.hs

This is not very, very clean (incomplete doc, for instance), but it'll do
the work.
By the way, the game.hs and client.hs are to be modified (it's the only way
to change the type of the players in the game)

2010/4/15 Limestraël limestr...@gmail.com

 Ok, but there is no function such as mapMonad in the operational package?

 By the way, I noticed that ProgramT is not automatically made instance of
 MonadIO when possible. It could be:
 instance (MonadIO m) = MonadIO (ProgramT r m) where
 liftIO = lift . liftIO

 Is that intentional?
 ( In fact, I think it's a slip in the mtl package itself, since every
 instance of MonadTrans can be declared instance of MonadIO:
 instance (MonadTrans t, MonadIO m) = MonadIO (t m) where
 liftIO = lift . liftIO
 )

 By the way, I finally managed to use operational to modify my TicTacToe
 game.
 (One shot, by the way, I had no bugs ^^. Very nice when it happens...)
 Human player and AI are working. I'm currently fixing the Network player.
 If you are interested, I could upload my code (it can be another example of
 how to use the operational package).

 In the end, I used a mix of your solution and my former one.
 I have a Request datatype:
 data Request a where
   GetGrid   :: Request Grid
   TurnDone  :: (Grid, Maybe GridResult) - Request ()
   GetResult :: Request (Maybe GridResult)

 (Grid is what you called Board, GridResult is a type which indicates if
 someone wins or if there is a draw)

 The game monad is PlayerMonadT, and is a newtype:

 newtype PlayerMonadT m a = PMT (ProgramT Request m a)
   deriving (Functor, Monad, MonadTrans)

 I still have a datatype Player, which contains functions: (I tried to use
 classes, but it was more complicated)

 data Player m m' = Player {
   -- | Gets the mark (Cross or Circle) of the player
   plMark  :: Mark,
   -- | Called when the player must play
   plTurn  :: Grid - m Pos,
   -- | Called when player tries to play at a forbidden position
   plForbidden :: Pos - m (),
   -- | Called when game has ended.
   plGameOver  :: GridResult - m (),
   -- | Used to reach PlayerMonad in the monad stack
   plLift  :: forall a. PlayerMonadT m' a - m a,
   -- | Used to run the monad stack the player runs in
   plRun   :: forall a. m a - PlayerMonadT m' a
 }

 *m* is the monad stack the player runs in. It must be able to run it, by
 providing a plRun function.
 *m'* is the top monad, which can't be run (IO for human, any monad for AI,
 etc.)
 The alteration done to this type is the addition of the plLift and plRun
 functions. Those are the functions you, Heinrich, and Bertram told me about.

 Then, *all* the players play according to this logic:

 playerLogic :: (Monad m) = Player m m' - m ()
 playerLogic pl = do
   let toProg = plLift pl . PMT . singleton
   grid - toProg GetGrid
   pos - plTurn pl grid
   case checkCell grid (plMark pl) pos of
 Nothing - do-- The cell was already filled in
   plForbidden pl pos -- We signal the error
   playerLogic pl -- We start the turn again
 Just newGridAndResult - do
  -- The cell has been successfully marked, so we
 got a new grid
   toProg $ TurnDone newGridAndResult
  -- At this point, the interpreter will switch to
 the other player
   mbResult - toProg $ GetResult
  -- This player is back, and wants to know what's
 new
   case mbResult of
 Nothing  - playerLogic pl
 Just res - plGameOver pl res

 We can then run this function with the player custom stack thanks to the
 runPlayer function:
 runPlayer :: (Monad m) = Player m m' - PlayerMonadT m' ()
 runPlayer pl = plRun pl $ playerLogic pl

 And finally, the interpreter:
 doGame :: (Monad m) = Grid - [PlayerMonadT m ()] - m Grid
 doGame initGrid players =
   mapM unwrap players = flip evalStateT (initGrid, Nothing) . eval
   where
 unwrap (PMT pl) = viewT pl

 eval :: (Monad m) = [PromptT Request m ()] - StateT (Grid, Maybe
 GridResult) m Grid

 eval [] = liftM fst get

 eval ((Return _) : pls) = eval pls

 eval ((GetGrid := pl) : pls) = do
   (grid, _) - get
   p - lift . viewT $ pl grid
   eval $ p : pls

 eval ((TurnDone (newGrid, mbResult) := pl) : pls) = do
   put (newGrid, mbResult)
   p - lift . viewT $ pl ()
   eval $ pls ++ [p]

 eval ((GetResult := pl) : pls) = do
   (_, mbResult) - get
   p - lift . viewT $ pl mbResult
   eval $ p : pls

 The game can be launched by doing for example:
 let pl1 = humanPlayer Cross
 let pl2 = artificialPlayer Circle levelOfDifficulty
 doGame blankGrid [runPlayer pl1, runPlayer pl2]

 I did it!

 2010/4/15 Heinrich 

[Haskell-cafe] Re: Fwd: Re: Simple game: a monad for each player

2010-04-15 Thread Heinrich Apfelmus
Limestraël wrote:
 I'd like to make it very accessible, so please don't hesitate to report
 any difficulties with finding and understanding documentation and examples!

 Then I think the name 'Prompt' may be misleading for those who doesn't know
 the MonadPrompt package. Maybe something like 'ProgramView' ?

Very good point. I'll change that in a future version.

 Ok, but there is no function such as mapMonad in the operational package?

No, not yet, but I'll probably add it, or at least its lesser cousin

liftT :: Program instr a - ProgramT instr m a

to a future version of the library. Still pondering.

 By the way, I noticed that ProgramT is not automatically made instance of
 MonadIO when possible. It could be:
 instance (MonadIO m) = MonadIO (ProgramT r m) where
 liftIO = lift . liftIO
 
 Is that intentional?

Yes and no. I refrained from making instances for the  mtl  classes
because I have not clearly thought about the design consequences yet.

I think that monad transformers are not the last word on modular
computational effects yet and I don't want to paint myself into a
corner. For example, as you note, the MonadIO instance could be deduced
automatically from the  MonadTrans  instance.

Of course, if I make  operational  interoperable with the  mtl , then I
better adhere to its style even if I'm not entirely happy with it.

 By the way, I finally managed to use operational to modify my TicTacToe
 game.

Yay! :D

 (One shot, by the way, I had no bugs ^^. Very nice when it happens...)
 Human player and AI are working. I'm currently fixing the Network player.
 If you are interested, I could upload my code (it can be another example of
 how to use the operational package).

Sending me / uploading your TicTacToe code would be great! I probably
won't use it verbatim, but try to simplify it a bit to turn it into
another easy to understand example of how to use  operational .


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe