I'm still not sure you're thinking about this the right way. Maybe it would help to see a working version (although not a *good* working version).
This e-mail is a literate haskell program, copy everything from the next line till the EOF into nim.lhs and run it.
----
Import the modules we need.

> import Control.Monad
> import System.Random

Define the types we're going to be using.

> data PileName = A | B | C deriving (Show, Eq, Read)
> type State = [Int]
> type Move = (PileName, Int)

initNim setups a new random game State.

> initNim :: IO State
> initNim = replicateM 3 $ randomRIO (1,10)

doMove takes a Move, and a initial State
and returns the updated game State after the Move.

> doMove :: Move -> State -> State
> doMove (A,x) xs = zipWith (-) xs [x,0,0]
> doMove (B,x) xs = zipWith (-) xs [0,x,0]
> doMove (C,x) xs = zipWith (-) xs [0,0,x]

getMove returns the next Move.

> getMove :: IO Move
> getMove = do
>     putStrLn "Which pile A, B, or C?"
>     x <- readLn
>     putStrLn "How many stones?"
>     y <- readLn
>     return (x,y)

checkWin takes a State and returns whether the game
has been won or not.

> checkWin :: State -> Bool
> checkWin [1,0,0] = True
> checkWin [0,1,0] = True
> checkWin [0,0,1] = True
> checkWin _       = False

doRound takes the current game State, performs one
round of play, and returns the updated State.

> doRound :: State -> IO State
> doRound oldState = do
>     putStrLn . show $ oldState
>     move <- getMove
>     let newState = doMove move oldState
>     return newState

untilM is a little helper function. To understand
what it does take a look at the until function
defined in Prelude. untilM does the same thing
but inside of a Monad (in this case IO). The
short version is that it runs the second function
it's given until the first function returns True.

> untilM :: (Mona m) => (a -> Bool) -> (a -> m a) -> a -> m a
> untilM p f x | p x = return x | otherwise = f x >>= untilM p f

The main ties everything together by initializing
the starting state, and then kicking off the
doRound loop (via untilM).

> main :: IO ()
> main = do
>     state <- initNim
>     untilM checkWin doRound state
>     putStrLn "You win!"

Areas for improvement include the following:

No error checking on user input, if you enter an invalid pile or
something that isn't a number (or is more then the number
of stones in the pile) bad things happen (hint: lookup try
catch and exception handling tutorials)

The checkWin function, the doMove, and the doRound
function don't do any sort of check to make sure the number
of stones removed can actually be removed (that is, none
of the piles go negative), nor is there a check done for
if *all* stones get removed.

It might be educational to change the type of State from
[Int] to (Int, [Int]) with the first value being the number of the
player who's turn it is. Adjust the various functions to
accept the new type of State and to update it appropriately.

----
EOF

-R. Kyle Murphy
--
Curiosity was framed, Ignorance killed the cat.


On Tue, Oct 27, 2009 at 08:39, John Moore <john.moore54@gmail.com> wrote:
Hi getting there with nimprogram well have it working in different areas.
 
The last part is where the most trouble is

import Control.Monad

import System.Random

 

initNim :: IO [Int]

initNim = replicateM 3 $ randomRIO (1,10)--- This get the random numbers

 

 

data PileName = A | B | C deriving (Show, Eq, Read)

 

typeOfMove :: (PileName, Int) -> [Int] -> [Int]

typeOfMove (A, x) xs = zipWith (-) xs [x,0,0]

typeOfMove (B, x) xs = zipWith (-) xs [0,x,0]

typeOfMove (C, x) xs = zipWith (-) xs [0,0,x]

 

main :: IO ()

main = do

    putStrLn "Which pile A, B, or C ?"

    x <- readLn

    putStrLn "How many stones?"

    y <- readLn

    let z = typeOfMove (x,y) [9,9,9]-- cannot get the random numbers here

    putStrLn . show $ z

 

 

 This is where the main problem is I 'm trying to run the game?

play nim = do

  z <- getLine

             newAnswer <- return (diff z)

if newAnswer == [0,0,1]||[0,1,0]||[1,0,0]

                 then putStrn "You win"

                 else play nim newAnswer

 

diff z ws hs =[ if z==w then w else h]-- trying to return different list here

 

 

John


_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners