"Haskell" way of modifying a character in an array of strings? - haskell

I'm not sure if our assignment was presented in the most functional-enabling of ways, but I have to work with it. I have a "map" that represents a pacman game state:
B B B B
B P _ B
B . . B
B B B B
where B is a border tile, P is pacman, _ is an empty space, and . is a food pellet. There are many rules when moving pacman, but consider one:
When pacman moves into a tile occupied by a food pellet, replace the pacman tile with an empty space and the food pellet with pacman. This function would have the definition:
move:: [[Char]] -> [[Char]]
Right now I've got functions that give me the (x,y) coordinate tuple of pacman and his new location, and I was planning to use the !! function to "overwrite" the tiles. However, I know a little of list operations such as :. Could I use : to accomplish this task?

Rather than modify the string, I would instead define a function of type:
type Position = (Int, Int)
type Board = [[Char]]
renderBoard :: Position -> Board
Then I would just modify pacman's position and re-render the board:
move :: Position -> Position
Edit: To answer your specific question, you can do this easily using the lens library:
import Control.Lens
move :: Position -> Position -> Board -> Board
move (oldX, oldY) (newX, newY) = (ix oldX.ix oldY .~ '_') . (ix newX.ix newY .~ 'P')

Below is a replace function that you can use to replace a particular position character in the 2d array [[Char]]
replace :: [[Char]] -> (Int,Int) -> Char -> [[Char]]
replace chars (x',y') c = do
(x,row) <- zip [0..] chars
return [if x == x' && y == y' then c else r | (y,r) <- zip [0..] row]
The second argument is the position which needs to be updated with the Char value in 3rd position.
Using this function you should be able to implement your move function.

Here's a simple approach that doesn't rely on libraries. First, we define a function .~ that allows you to set the index of a list -
set n x xs = take n xs ++ (x : drop (n+1) xs)
and give it a convenient alias so that we can use it in infix form.
n .~ x = \xs -> set n x xs
This allows you to do things like
>> let list = [1,2,3,4]
>> 1 .~ 10 $ list
[1,10,3,4]
Now it's a simple matter to extend that to a function that modifies two-dimensional lists
(n,m) .= x = \xs -> n .~ (m .~ x $ xs!!n) $ xs
so that you can do things like
>> let listOfList = [[1,2,3],[4,5,6],[7,8,9]]
>> (1,1) .= 100 $ listOfList
[[1,2,3],[4,100,6],[7,8,9]]
Now you can easily write a function move that takes an old position, a new position and the current board, and modifies the board in the way you want
type Pos = (Int,Int)
type Board = [[Char]]
move :: Pos -> Pos -> Board -> Board
move (x,y) (x',y') board = board''
where
board' = (x, y ) .= '_' $ board
board'' = (x',y') .= 'P' $ board'
That is, the first line in the where clause modifies the board to replace PacMan's old position with an empty space, and the second line modifies the board that's reutrned form that, to put PacMan in the new position.

Related

How to randomly shuffle a list

I have random number generator
rand :: Int -> Int -> IO Int
rand low high = getStdRandom (randomR (low,high))
and a helper function to remove an element from a list
removeItem _ [] = []
removeItem x (y:ys) | x == y = removeItem x ys
| otherwise = y : removeItem x ys
I want to shuffle a given list by randomly picking an item from the list, removing it and adding it to the front of the list. I tried
shuffleList :: [a] -> IO [a]
shuffleList [] = []
shuffleList l = do
y <- rand 0 (length l)
return( y:(shuffleList (removeItem y l) ) )
But can't get it to work. I get
hw05.hs:25:33: error:
* Couldn't match expected type `[Int]' with actual type `IO [Int]'
* In the second argument of `(:)', namely
....
Any idea ?
Thanks!
Since shuffleList :: [a] -> IO [a], we have shuffleList (xs :: [a]) :: IO [a].
Obviously, we can't cons (:) :: a -> [a] -> [a] an a element onto an IO [a] value, but instead we want to cons it onto the list [a], the computation of which that IO [a] value describes:
do
y <- rand 0 (length l)
-- return ( y : (shuffleList (removeItem y l) ) )
shuffled <- shuffleList (removeItem y l)
return y : shuffled
In do notation, values to the right of <- have types M a, M b, etc., for some monad M (here, IO), and values to the left of <- have the corresponding types a, b, etc..
The x :: a in x <- mx gets bound to the pure value of type a produced / computed by the M-type computation which the value mx :: M a denotes, when that computation is actually performed, as a part of the combined computation represented by the whole do block, when that combined computation is performed as a whole.
And if e.g. the next line in that do block is y <- foo x, it means that a pure function foo :: a -> M b is applied to x and the result is calculated which is a value of type M b, denoting an M-type computation which then runs and produces / computes a pure value of type b to which the name y is then bound.
The essence of Monad is thus this slicing of the pure inside / between the (potentially) impure, it is these two timelines going on of the pure calculations and the potentially impure computations, with the pure world safely separated and isolated from the impurities of the real world. Or seen from the other side, the pure code being run by the real impure code interacting with the real world (in case M is IO). Which is what computer programs must do, after all.
Your removeItem is wrong. You should pick and remove items positionally, i.e. by index, not by value; and in any case not remove more than one item after having picked one item from the list.
The y in y <- rand 0 (length l) is indeed an index. Treat it as such. Rename it to i, too, as a simple mnemonic.
Generally, with Haskell it works better to maximize the amount of functional code at the expense of non-functional (IO or randomness-related) code.
In your situation, your “maximum” functional component is not removeItem but rather a version of shuffleList that takes the input list and (as mentioned by Will Ness) a deterministic integer position. List function splitAt :: Int -> [a] -> ([a], [a]) can come handy here. Like this:
funcShuffleList :: Int -> [a] -> [a]
funcShuffleList _ [] = []
funcShuffleList pos ls =
if (pos <=0) || (length(take (pos+1) ls) < (pos+1))
then ls -- pos is zero or out of bounds, so leave list unchanged
else let (left,right) = splitAt pos ls
in (head right) : (left ++ (tail right))
Testing:
λ>
λ> funcShuffleList 4 [0,1,2,3,4,5,6,7,8,9]
[4,0,1,2,3,5,6,7,8,9]
λ>
λ> funcShuffleList 5 "#ABCDEFGH"
"E#ABCDFGH"
λ>
Once you've got this, you can introduce randomness concerns in simpler fashion. And you do not need to involve IO explicitely, as any randomness-friendly monad will do:
shuffleList :: MonadRandom mr => [a] -> mr [a]
shuffleList [] = return []
shuffleList ls =
do
let maxPos = (length ls) - 1
pos <- getRandomR (0, maxPos)
return (funcShuffleList pos ls)
... IO being just one instance of MonadRandom.
You can run the code using the default IO-hosted random number generator:
main = do
let inpList = [0,1,2,3,4,5,6,7,8]::[Integer]
putStrLn $ "inpList = " ++ (show inpList)
-- mr automatically instantiated to IO:
outList1 <- shuffleList inpList
putStrLn $ "outList1 = " ++ (show outList1)
outList2 <- shuffleList outList1
putStrLn $ "outList2 = " ++ (show outList2)
Program output:
$ pickShuffle
inpList = [0,1,2,3,4,5,6,7,8]
outList1 = [6,0,1,2,3,4,5,7,8]
outList2 = [8,6,0,1,2,3,4,5,7]
$
$ pickShuffle
inpList = [0,1,2,3,4,5,6,7,8]
outList1 = [4,0,1,2,3,5,6,7,8]
outList2 = [2,4,0,1,3,5,6,7,8]
$
The output is not reproducible here, because the default generator is seeded by its launch time in nanoseconds.
If what you need is a full random permutation, you could have a look here and there - Knuth a.k.a. Fisher-Yates algorithm.

Matrix of string, with unique columns and rows, latin square

i'm trying to write a function that for n gives matrix n*n with unique rows and columns (latin square).
I got function that gives my list of strings "1" .. "2" .. "n"
numSymbol:: Int -> [String]
I tried to generate all permutations of this, and them all n-length tuples of permutations, and them check if it is unique in row / columns. But complexity (n!)^2 works perfect for 2 and 3, but with n > 3 it takes forever. It is possible to build latin square from permutations directly, for example from
permutation ( numSymbol 3) = [["1","2","3"],["1","3","2"],["2","1","3"],["2","3","1"],["3","1","2"],["3","2","1"]]
get
[[["1","2","3",],["2","1","3"],["3","1","2"]] , ....]
without generating list like [["1",...],["1",...],...], when we know first element disqualify it ?
Note: since we can easily take a Latin square that's been filled with numbers from 1 to n and re-label it with anything we want, we can write code that uses integer symbols without giving anything away, so let's stick with that.
Anyway, the stateful backtracking/nondeterministic monad:
type StateList s = StateT s []
is helpful for this sort of problem.
Here's the idea. We know that every symbol s is going to appear exactly once in each row r, so we can represent this with an urn of all possible ordered pairs (r,s):
my_rs_urn = [(r,s) | r <- [1..n], s <- [1..n]]
Similarly, as every symbol s appears exactly once in each column c, we can use a second urn:
my_cs_urn = [(c,s) | c <- [1..n], s <- [1..n]]
Creating a Latin square is matter of filling in each position (r,c) with a symbol s by removing matching balls (r,s) and (c,s) (i.e., removing two balls, one from each urn) so that every ball is used exactly once. Our state will be the content of the urns.
We need backtracking because we might reach a point where for a particular position (r,c), there is no s such that (r,s) and (c,s) are both still available in their respective urns. Also, a pleasant side-effect of list-based backtracking/nondeterminism is that it'll generate all possible Latin squares, not just the first one it finds.
Given this, our state will look like:
type Urn = [(Int,Int)]
data S = S
{ size :: Int
, rs :: Urn
, cs :: Urn }
I've included the size in the state for convenience. It won't ever be modified, so it actually ought to be in a Reader instead, but this is simpler.
We'll represent a square by a list of cell contents in row-major order (i.e., the symbols in positions [(1,1),(1,2),...,(1,n),(2,1),...,(n,n)]):
data Square = Square
Int -- square size
[Int] -- symbols in row-major order
deriving (Show)
Now, the monadic action to generate latin squares will look like this:
type M = StateT S []
latin :: M Square
latin = do
n <- gets size
-- for each position (r,c), get a valid symbol `s`
cells <- forM (pairs n) (\(r,c) -> getS r c)
return $ Square n cells
pairs :: Int -> [(Int,Int)]
pairs n = -- same as [(x,y) | x <- [1..n], y <- [1..n]]
(,) <$> [1..n] <*> [1..n]
The worker function getS picks an s so that (r,s) and (c,s) are available in the respective urns, removing those pairs from the urns as a side effect. Note that getS is written non-deterministically, so it'll try every possible way of picking an s and associated balls from the urns:
getS :: Int -> Int -> M Int
getS r c = do
-- try each possible `s` in the row
s <- pickSFromRow r
-- can we put `s` in this column?
pickCS c s
-- if so, `s` is good
return s
Most of the work is done by the helpers pickSFromRow and pickCS. The first, pickSFromRow picks an s from the given row:
pickSFromRow :: Int -> M Int
pickSFromRow r = do
balls <- gets rs
-- "lift" here non-determinstically picks balls
((r',s), rest) <- lift $ choices balls
-- only consider balls in matching row
guard $ r == r'
-- remove the ball
modify (\st -> st { rs = rest })
-- return the candidate "s"
return s
It uses a choices helper which generates every possible way of pulling one element out of a list:
choices :: [a] -> [(a,[a])]
choices = init . (zipWith f <$> inits <*> tails)
where f a (x:b) = (x, a++b)
f _ _ = error "choices: internal error"
The second, pickCS checks if (c,s) is available in the cs urn, and removes it if it is:
pickCS :: Int -> Int -> M ()
pickCS c s = do
balls <- gets cs
-- only continue if the required ball is available
guard $ (c,s) `elem` balls
-- remove the ball
modify (\st -> st { cs = delete (c,s) balls })
With an appropriate driver for our monad:
runM :: Int -> M a -> [a]
runM n act = evalStateT act (S n p p)
where p = pairs n
this can generate all 12 Latin square of size 3:
λ> runM 3 latin
[Square 3 [1,2,3,2,3,1,3,1,2],Square 3 [1,2,3,3,1,2,2,3,1],...]
or the 576 Latin squares of size 4:
λ> length $ runM 4 latin
576
Compiled with -O2, it's fast enough to enumerate all 161280 squares of size 5 in a couple seconds:
main :: IO ()
main = print $ length $ runM 5 latin
The list-based urn representation above isn't very efficient. On the other hand, because the lengths of the lists are pretty small, there's not that much to be gained by finding more efficient representations.
Nonetheless, here's complete code that uses efficient Map/Set representations tailored to the way the rs and cs urns are used. Compiled with -O2, it runs in constant space. For n=6, it can process about 100000 Latin squares per second, but that still means it'll need to run for a few hours to enumerate all 800 million of them.
{-# OPTIONS_GHC -Wall #-}
module LatinAll where
import Control.Monad.State
import Data.List
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Map (Map, (!))
import qualified Data.Map as Map
data S = S
{ size :: Int
, rs :: Map Int [Int]
, cs :: Set (Int, Int) }
data Square = Square
Int -- square size
[Int] -- symbols in row-major order
deriving (Show)
type M = StateT S []
-- Get Latin squares
latin :: M Square
latin = do
n <- gets size
cells <- forM (pairs n) (\(r,c) -> getS r c)
return $ Square n cells
-- All locations in row-major order [(1,1),(1,2)..(n,n)]
pairs :: Int -> [(Int,Int)]
pairs n = (,) <$> [1..n] <*> [1..n]
-- Get a valid `s` for position `(r,c)`.
getS :: Int -> Int -> M Int
getS r c = do
s <- pickSFromRow r
pickCS c s
return s
-- Get an available `s` in row `r` from the `rs` urn.
pickSFromRow :: Int -> M Int
pickSFromRow r = do
urn <- gets rs
(s, rest) <- lift $ choices (urn ! r)
modify (\st -> st { rs = Map.insert r rest urn })
return s
-- Remove `(c,s)` from the `cs` urn.
pickCS :: Int -> Int -> M ()
pickCS c s = do
balls <- gets cs
guard $ (c,s) `Set.member` balls
modify (\st -> st { cs = Set.delete (c,s) balls })
-- Return all ways of removing one element from list.
choices :: [a] -> [(a,[a])]
choices = init . (zipWith f <$> inits <*> tails)
where f a (x:b) = (x, a++b)
f _ _ = error "choices: internal error"
-- Run an action in the M monad.
runM :: Int -> M a -> [a]
runM n act = evalStateT act (S n rs0 cs0)
where rs0 = Map.fromAscList $ zip [1..n] (repeat [1..n])
cs0 = Set.fromAscList $ pairs n
main :: IO ()
main = do
print $ runM 3 latin
print $ length (runM 4 latin)
print $ length (runM 5 latin)
Somewhat remarkably, modifying the program to produce only reduced Latin squares (i.e., with symbols [1..n] in order in both the first row and the first column) requires changing only two functions:
-- All locations in row-major order, skipping first row and column
-- i.e., [(2,2),(2,3)..(n,n)]
pairs :: Int -> [(Int,Int)]
pairs n = (,) <$> [2..n] <*> [2..n]
-- Run an action in the M monad.
runM :: Int -> M a -> [a]
runM n act = evalStateT act (S n rs0 cs0)
where -- skip balls [(1,1)..(n,n)] for first row
rs0 = Map.fromAscList $ map (\r -> (r, skip r)) [2..n]
-- skip balls [(1,1)..(n,n)] for first column
cs0 = Set.fromAscList $ [(c,s) | c <- [2..n], s <- skip c]
skip i = [1..(i-1)]++[(i+1)..n]
With these modifications, the resulting Square will include symbols in row-major order but skipping the first row and column. For example:
λ> runM 3 latin
[Square 3 [3,1,1,2]]
means:
1 2 3 fill in question marks 1 2 3
2 ? ? =====================> 2 3 1
3 ? ? in row-major order 3 1 2
This is fast enough to enumerate all 16,942,080 reduced Latin squares of size 7 in a few minutes:
$ stack ghc -- -O2 -main-is LatinReduced LatinReduced.hs && time ./LatinReduced
[1 of 1] Compiling LatinReduced ( LatinReduced.hs, LatinReduced.o )
Linking LatinReduced ...
16942080
real 3m9.342s
user 3m8.494s
sys 0m0.848s

Haskell print out 2d array

I'm trying to print out my 2d array in game of life, but i'm not quite sure how to go on with it. So I need some help with my printArray function I'm not quite sure how to proceed. Her is the code below, everything is working.. Except printing it out in the right manner.
module GameOfLife where
import Data.List
import System.IO
import Text.Show
import Data.Array
import System.Random
width :: Int
width = 5
height :: Int
height = 5
data State = Alive | Dead deriving (Eq, Show)
type Pos = (Int,Int)
type Board = Array Pos State
startBoard :: Pos -> Board
startBoard (width,height) =
let bounds = ((0,0),(width - 1,height - 1))
in array bounds $ zip (range bounds) (repeat Dead)
set :: Board -> [(Pos,State)] -> Board
set = (//)
get :: Board -> [Pos] -> [State]
get board pos = map (board!) pos
neighbours :: Board -> Pos -> [Pos]
neighbours board c#(x,y) =
filter (/= c) $ filter (inRange (bounds board)) [(x',y') | x' <- [x -
1..x + 1], y' <- [y - 1..y + 1]]
nextGen :: Board -> Board
nextGen board =(irrelevant code for the question..)
printArray :: Board -> String
printArray arr =
unlines [unwords [show (arr ! (x, y)) | x <- [1..5]] | y <- [1..5]]
My output:
[((0,0),Dead),((0,1),Dead),((0,2),Dead),((0,3),Dead),((1,0),Dead),
((1,1),Dead),((1,2),Dead),((1,3),Dead),((2,0),Dead),((2,1),Dead),
((2,2),Dead)2,3),Dead)]
My preferable output:
1 2 3 4 5
1 . . . . .
2 n n n . .
3 n X n . .
4 n n n . .
5 . . . . .
To start to answer your question, I suggest breaking the problem into several pieces:
Print out the numbers across the top.
Number each row as you print them.
Decide what symbol to print in each cell.
Tackle each of these pieces one at a time. If it helps, rather than think in terms of "printing" just build up a String object. Once you have a String, printing is pretty trivial.

Non-tree data structures in Haskell

Making tree like data structures is relatively easy in Haskell. However, what if I want a structure like the following:
A (root)
/ \
B C
/ \ / \
D E F
So if I traverse down the structure through B to update E, the returned new updated structure also has E updated if I traverse through C.
Could someone give me some hints about how to achieve this? You can assume there are no loops.
I would flatten the data structure to an array, and operate on this instead:
import Data.Array
type Tree = Array Int -- Bounds should start at (1) and go to sum [1..n]
data TreeTraverse = TLeft TreeTraverse | TRight TreeTraverse | TStop
Given some traverse directions (left, right, stop), it's easy to see that if we go left, we simply add the current level to our position, and if we go right, we also add the current position plus one:
getPosition :: TreeTraverse -> Int
getPosition = getPosition' 1 1
where
getPosition' level pos (TLeft ts) = getPosition' (level+1) (pos+level) ts
getPosition' level pos (TRight ts) = getPosition' (level+1) (pos+level + 1) ts
getPosition' _ pos (TStop) = pos
In your case, you want to traverse either ABE or ACE:
traverseABE = TLeft $ TRight TStop
traverseACE = TRight $ TLeft TStop
Since we already now how to get the position of your element, and Data.Array provides some functions to set/get specific elements, we can use the following functions to get/set tree values:
getElem :: TreeTraverse -> Tree a -> a
getElem tt t = t ! getPosition tt
setElem :: TreeTraverse -> Tree a -> a -> Tree a
setElem tt t x = t // [(getPosition tt, x)]
To complete the code, lets use your example:
example = "ABCDEF"
exampleTree :: Tree Char
exampleTree = listArray (1, length example) example
And put everything to action:
main :: IO ()
main = do
putStrLn $ "Traversing from A -> B -> E: " ++ [getElem traverseABE exampleTree]
putStrLn $ "Traversing from A -> C -> E: " ++ [getElem traverseACE exampleTree]
putStrLn $ "exampleTree: " ++ show exampleTree ++ "\n"
putStrLn $ "Setting element from A -> B -> E to 'X', "
let newTree = setElem traverseABE exampleTree 'X'
putStrLn $ "but show via A -> C -> E: " ++ [getElem traverseACE newTree]
putStrLn $ "newTree: " ++ show newTree ++ "\n"
Note that this is most-likely not the best way to do this, but the first thing that I had in mind.
Once you've established identity, it can be done.
But first you must establish identity.
In many languages, values can be distinct from each other, but equal. In Python, for example:
>>> a = [1]
>>> b = [1]
>>> a == b
True
>>> a is b
False
You want to update E in one branch of the tree, and also update all other elements for which that element is E. But Haskell is referentially transparent: it has no notion of things being the same object; only equality, and even that is not applicable for every object.
One way you could do this is equality. Say this was your tree:
__A__
/ \
B C
/ \ / \
1 2 2 3
Then we could go through the tree and update all the 2s to, say, four. But this isn't exactly what you want in some cases.
In Haskell, if you want to update one thing in multiple places, you'll have to be explicit about what is and isn't the same thing. Another way you could deal with this is to tag each different value with a unique integer, and use that integer to determine identity:
____________A___________
/ \
B C
/ \ / \
(id=1)"foo" (id=2)"bar" (id=2)"bar" (id=3)"baz"
Then we could update all values with an identity of 2. Accidental collisions cannot be a problem, as there can be no collisions except those that are intentional.
This is essentially what STRef and IORef do, except they hoist the actual value into the monad's state and hide the identities from you. The only downside of using these is you'll need to make much of your code monadic, but you're probably not going to get away from that easily whatever you do. (Modifying values rather than replacing them is an inherently effectful thing to do.)
The structure you gave was not specified in much detail so it's impossible to tailor an example to your use case, but here's a simple example using the ST monad and a Tree:
import Control.Monad
import Control.Monad.ST
import Data.Tree
import Data.Traversable (traverse)
import Data.STRef
createInitialTree :: ST s (Tree (STRef s String))
createInitialTree = do
[a, b, c, d, e, f] <- mapM newSTRef ["A", "B", "C", "D", "E", "F"]
return $ Node a [ Node b [Node d [], Node e []]
, Node c [Node e [], Node f []]
]
dereferenceTree :: Tree (STRef s a) -> ST s (Tree a)
dereferenceTree = traverse readSTRef
test :: ST s (Tree String, Tree String)
test = do
tree <- createInitialTree
before <- dereferenceTree tree
let leftE = subForest (subForest tree !! 0) !! 1
writeSTRef (rootLabel leftE) "new" -- look ma, single update!
after <- dereferenceTree tree
return (before, after)
main = do
let (before, after) = runST test
putStrLn $ drawTree before
putStrLn $ drawTree after
Observe that although we only explicitly modified the value of the left E value, it changed on the right side, too, as desired.
I should note that these are not the only ways. There are probably many other solutions to this same problem, but they all require you to define identity sensibly. Only once that has been done can one begin the next step.

Haskell Tic Tac Toe tuple board: How to generate possible moves?

So I have a Tic Tac Toe board, in the form of nested tuples, like so:
type Row = (Field, Field, Field)
type Board = (Row, Row, Row)
data Field = X | O | B
deriving (Eq, Ord)
Where B stands for empty. I need to take a player, a given board state, and then generate a list of all possible board states after the next move.
moves :: Player -> Board -> [Board]
However, I just can't figure it out. My initial thought is that I need to iterate through every field, to check whether or not it is empty, and then add a new Board to the list or do nothing. However, I see no way to iterate through all the fields. Even if I manually check every field with if statement or guards, how do I move onto the next field to check it, regardless of whether I end up with a possible move or not?
If I convert the board format into a list I could do it, but I feel like that defeats the purpose of this problem. There's got to be a better solution that doesn't require restructuring Board.
You're not going to be able to iterate through the fields of a tuple -- tuples aren't intended for that. A list of lists is probably a more natural representation for this problem.
That said, you can implement this function with the board representation you're using by following the types. A move on a Board is a move on either the first, second, or third row. A move on a row is the placement of the player on either the first, second, or third field. The difficulty with your representation is that there's no simple way to map over a tuple, since tuples are generally heterogeneous. So instead, one thing you can do is write yourself a generic way to apply a function to a location in a tuple. Here's one way to do that (if the Monad stuff confuses you, mentally substitute "list of foo" everywhere you see m foo and you'll be okay):
mReplace1 :: Monad m => (a -> m d) -> (a,b,c) -> m (d,b,c)
mReplace1 f (a,b,c) = f a >>= \d -> return (d,b,c)
mReplace2 :: Monad m => (b -> m d) -> (a,b,c) -> m (a,d,c)
mReplace2 f (a,b,c) = f b >>= \d -> return (a,d,c)
mReplace3 :: Monad m => (c -> m d) -> (a,b,c) -> m (a,b,d)
mReplace3 f (a,b,c) = f c >>= \d -> return (a,b,d)
These functions provide a way to apply a function to the first, second, and third slots in a tuple, respectively. They're wrapped in a monad so that we can have a function that returns a list of possibilities for the slot, and automatically convert that to a list of possibilities for the tuple as a whole.
With these, we can write the overall function just by stringing these calls together.
moves p board = mReplace1 rowMoves board ++
mReplace2 rowMoves board ++
mReplace3 rowMoves board
where rowMoves row = mReplace1 fieldMoves row ++
mReplace2 fieldMoves row ++
mReplace3 fieldMoves row
fieldMoves B = [p]
fieldMoves _ = []
That is: the moves for a board are all the possibilities for a move in row 1, plus all the possibilities for row 2, plust all the possibilities for row 3. For a given row, the possible moves are all the moves for slot 1, plus all the moves for slot 2, plus all the moves for slot 3. For a given slot, if there's already an X or an O there, then there are no possible moves; otherwise there's one possible move (placing the player in that slot).
Here's a simple solution that I've used before
import qualified Data.Map as Map
data Piece    = O | X deriving (Eq,Ord)
type Position = (Int,Int)
type Board = Map.Map Position Piece
positions = [(i,j) | i <- [0,1,2], j <- [0,1,2]]
spaces board = map (\pos -> Map.notMember pos board) positions
moves player board = map (\pos -> Map.insert pos player board) (spaces board)
As other people have stated, tuples is not a very good idea for this approach, since there is no way to traverse them.
You said you needed tuples, so there you go, I'm almost sure it works, test it.
First your code how I would've done it
import Control.Monad (msum)
import Control.Applicative ((<*>), pure)
data Player = P1 | P2 deriving (Eq, Show)
data Field = X | O | B deriving (Eq, Show)
type Board = ((Field,Field,Field)
,(Field,Field,Field)
,(Field,Field,Field))
symbolToPlayer :: Field -> Player
symbolToPlayer X = P1
symbolToPlayer O = P2
checkThree :: (Field,Field,Field) -> Maybe Player
checkThree (a,b,c)
| a == b && a == c = Just $ symbolToPlayer a
| otherwise = Nothing
winHorizontal :: Board -> Maybe Player
winHorizontal (r1, r2, r3) = msum $ map checkThree [r1, r2, r3]
winVertical :: Board -> Maybe Player
winVertical ((a,b,c), (d,e,f), (g,h,i)) =
msum $ map checkThree [(a,d,g), (b,e,h), (c,f,i)]
winDiagonal :: Board -> Maybe Player
winDiagonal ((a,_,c), (_,e,_), (g,_,i)) =
msum $ map checkThree [(a,e,i), (c,e,g)]
hasWinner :: Board -> Maybe Player
hasWinner b = msum $ [winHorizontal, winVertical, winHorizontal] <*> pure b
This is the part of nextStates function
boardBlanks :: Board -> Int
boardBlanks (r1,r2,r3) = rowBlanks r1 + rowBlanks r2 + rowBlanks r3
rowBlanks :: (Field, Field, Field) -> Int
rowBlanks (a,b,c) = foldr hack 0 [a,b,c]
where hack B c = 1 + c
hack _ c = c
changeBoard :: Field -> Int -> Board -> Board
changeBoard f i (a,b,c)
| hack [a] > i = (changeRow f (i - hack []) a, b, c)
| hack [a,b] > i = (a, changeRow f (i - hack [a]) b, c)
| hack [a,b,c] > i= (a, b, changeRow f (i - hack [a,b]) c)
where
hack ls = sum $ map rowBlanks ls
changeRow f 0 row =
case row of
(B,a,b) -> (f,a,b)
(a,B,b) -> (a,f,b)
(a,b,B) -> (a,b,f)
otherwise -> row
changeRow f 1 row =
case row of
(B,B,a) -> (B,f,a)
(a,B,B) -> (a,B,f)
otherwise -> row
changeRow f 2 row =
case row of
(B,B,B) -> (B,B,f)
otherwise -> row
nextStates :: Board -> [Board]
nextStates b = os ++ xs
where
os = foldr (hack O) [] . zip [0..] $ replicate (boardBlanks b) b
xs = foldr (hack X) [] . zip [0..] $ replicate (boardBlanks b) b
hack f (i,a) ls = changeBoard f i a : ls

Resources