[Haskell-cafe] Small question about something easy

2008-03-18 Thread iliali16

Hi guys I am a bit new to haskell but I am doing good till now. I have to
write a function that takes 2 inputs and then reutns one composite output.
Now my problem is that I have to make composition of that function meaning
that I  have to access in some way the output of the function before it is
really computed. I will show you part of my code which is working prefectly:

play :: Logo - TurtleState - (Image, TurtleState)

play DoNothing (pen, (x,y), angle) = (emptyImage, (pen, (x,y), angle))

play PenDown (pen, (x,y), angle) = (emptyImage,(pen, (x,y), angle))

play PenUp (pen, (x,y), angle) = (emptyImage,(pen, (x,y), angle))

play (Forward n) (pen, (x,y), angle) 
|pen == True = ((line (x,y) (x+n,y+n)), (True, (x+n,y+n), angle))
|otherwise = (emptyImage,(pen, (x+n,y+n), angle))

play (Turn n) (pen, (x,y), angle) = (emptyImage, (pen, (x,y), (angle+n)))

play (DoNothing :: p2) (pen, (x,y), angle) = play p2 (pen, (x,y), angle)
play (p1 : DoNothing) (pen, (x,y), angle) = play p1 (pen, (x,y), angle)
play (PenDown :: PenUp) (pen, (x,y), angle) = (emptyImage,(pen, (x,y),
angle))
play (PenDown :: (Forward n)) (pen, (x,y), angle) = play (Forward n) (True,
(x,y), angle)   
play (PenDown :: PenDown) (pen, (x,y), angle) = (emptyImage,(pen, (x,y),
angle))
play (PenDown :: (Turn n)) (pen, (x,y), angle) = play (Turn n) (pen, (x,y),
angle)
play (PenUp :: PenUp) (pen, (x,y), angle) = (emptyImage,(pen, (x,y),
angle))
play (PenUp :: (Forward n)) (pen, (x,y), angle) = play (Forward n) (False,
(x,y), angle) 
play (PenUp :: (Turn n)) (pen, (x,y), angle) = play (Turn n) (pen, (x,y),
angle)
play (PenUp :: PenDown) (pen, (x,y), angle) = (emptyImage,(pen, (x,y),
angle)) 

Now the problem comes here:
play (p1 :: p2) state 
 |play p1 state == (i1,state1)  play p2 state1 == (i2,state2)
= (i1+++i2,state2)

I know that if I manage to do that function the one above with this sign ::
do not need to be impelmented since this one will cater for all the cases.
Can you please help me?

Thanks in advance!
-- 
View this message in context: 
http://www.nabble.com/Small-question-about-something-easy-tp16119618p16119618.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Small question about something easy

2008-03-18 Thread Thomas Schilling


On 18 mar 2008, at 13.51, Luke Palmer wrote:


On Tue, Mar 18, 2008 at 12:24 PM, iliali16 [EMAIL PROTECTED] wrote:

 Now the problem comes here:
 play (p1 :: p2) state
 |play p1 state == (i1,state1)  play p2 state1 ==  
(i2,state2)

 = (i1+++i2,state2)

 I know that if I manage to do that function the one above with  
this sign ::
 do not need to be impelmented since this one will cater for all  
the cases.

 Can you please help me?


You just need a nice simple let or where clause:

  play (p1 :: p2) state = (i1 +++ i2, state2)
where
(i1,state1) = play p1 state
(i2,state2) = play p2 state1

Or equivalently:

  play (p1 :: p2) state =
let (i1, state1) = play p1 state
(i2, state2) = play p2 state1
in (i1 +++ i2, state2)

And there's nothing lazily recursive about these, just the information
usage is a little more complex.  But it could be implemented perfectly
naturally in scheme, for example.

For further exploration: the pattern here where the state is threaded
through different computations, is captured by the module
Control.Monad.State. So if play returned an object of a State monad,
such as:

  play :: Logo - State TurtleState Image

Then this case could be implemented as:

  play (p1 :: p2) = do
i1 - play p1
i2 - play p2
return (i1 +++ i2)

Pretty, ain't it?  A little too pretty if you ask me.  Let's make it
uglier and shorter still:

  play (p1 :: p2) = liftM2 (+++) (play p1) (play p2)



Or use Applicative directly:

  play (p1 :: p2) = (+++) $ play p1 * play p2
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Small question about something easy

2008-03-18 Thread Luke Palmer
On Tue, Mar 18, 2008 at 12:24 PM, iliali16 [EMAIL PROTECTED] wrote:
  Now the problem comes here:
  play (p1 :: p2) state
  |play p1 state == (i1,state1)  play p2 state1 == (i2,state2)
  = (i1+++i2,state2)

  I know that if I manage to do that function the one above with this sign ::
  do not need to be impelmented since this one will cater for all the cases.
  Can you please help me?

You just need a nice simple let or where clause:

  play (p1 :: p2) state = (i1 +++ i2, state2)
where
(i1,state1) = play p1 state
(i2,state2) = play p2 state1

Or equivalently:

  play (p1 :: p2) state =
let (i1, state1) = play p1 state
(i2, state2) = play p2 state1
in (i1 +++ i2, state2)

And there's nothing lazily recursive about these, just the information
usage is a little more complex.  But it could be implemented perfectly
naturally in scheme, for example.

For further exploration: the pattern here where the state is threaded
through different computations, is captured by the module
Control.Monad.State. So if play returned an object of a State monad,
such as:

  play :: Logo - State TurtleState Image

Then this case could be implemented as:

  play (p1 :: p2) = do
i1 - play p1
i2 - play p2
return (i1 +++ i2)

Pretty, ain't it?  A little too pretty if you ask me.  Let's make it
uglier and shorter still:

  play (p1 :: p2) = liftM2 (+++) (play p1) (play p2)

:-)

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


Re: [Haskell-cafe] Small question about something easy

2008-03-18 Thread iliali16

Thanks to all of you I got it I was missing the notation. Thanks again! 

iliali16 wrote:
 
 Hi guys I am a bit new to haskell but I am doing good till now. I have to
 write a function that takes 2 inputs and then reutns one composite output.
 Now my problem is that I have to make composition of that function meaning
 that I  have to access in some way the output of the function before it is
 really computed. I will show you part of my code which is working
 prefectly:
 
 play :: Logo - TurtleState - (Image, TurtleState)
 
 play DoNothing (pen, (x,y), angle) = (emptyImage, (pen, (x,y), angle))
 
 play PenDown (pen, (x,y), angle) = (emptyImage,(pen, (x,y), angle))
 
 play PenUp (pen, (x,y), angle) = (emptyImage,(pen, (x,y), angle))
   
 play (Forward n) (pen, (x,y), angle) 
   |pen == True = ((line (x,y) (x+n,y+n)), (True, (x+n,y+n), angle))
   |otherwise = (emptyImage,(pen, (x+n,y+n), angle))
 
 play (Turn n) (pen, (x,y), angle) = (emptyImage, (pen, (x,y), (angle+n)))
 
 play (DoNothing :: p2) (pen, (x,y), angle) = play p2 (pen, (x,y), angle)
 play (p1 : DoNothing) (pen, (x,y), angle) = play p1 (pen, (x,y), angle)
 play (PenDown :: PenUp) (pen, (x,y), angle) = (emptyImage,(pen, (x,y),
 angle))
 play (PenDown :: (Forward n)) (pen, (x,y), angle) = play (Forward n)
 (True, (x,y), angle)  
 play (PenDown :: PenDown) (pen, (x,y), angle) = (emptyImage,(pen, (x,y),
 angle))
 play (PenDown :: (Turn n)) (pen, (x,y), angle) = play (Turn n) (pen,
 (x,y), angle)
 play (PenUp :: PenUp) (pen, (x,y), angle) = (emptyImage,(pen, (x,y),
 angle))
 play (PenUp :: (Forward n)) (pen, (x,y), angle) = play (Forward n)
 (False, (x,y), angle) 
 play (PenUp :: (Turn n)) (pen, (x,y), angle) = play (Turn n) (pen, (x,y),
 angle)
 play (PenUp :: PenDown) (pen, (x,y), angle) = (emptyImage,(pen, (x,y),
 angle)) 
 
 Now the problem comes here:
 play (p1 :: p2) state 
  |play p1 state == (i1,state1)  play p2 state1 ==
 (i2,state2) = (i1+++i2,state2)
 
 I know that if I manage to do that function the one above with this sign
 :: do not need to be impelmented since this one will cater for all the
 cases. Can you please help me?
 
 Thanks in advance!
 
:jumping::jumping::jumping::jumping::jumping::jumping::jumping::jumping::jumping::jumping::jumping::jumping::jumping::jumping:
-- 
View this message in context: 
http://www.nabble.com/Small-question-about-something-easy-tp16119618p16121996.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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