[Haskell-beginners] Dipping Toes Into Haskell

Bob Hutchison hutch-lists at recursive.ca
Tue Mar 24 13:13:03 UTC 2015


> On Mar 23, 2015, at 10:38 PM, Timothy Washington <twashing at gmail.com> wrote:
> 

[snip]

> So ultimately I want a function signature that lets me pass in a lens position. 
> 
> -- 1. these 2 don't compile together
> 
> data Position = Position Int Int deriving Show 
> 
> move :: Board -> Piece -> Position -> Board
> move board piece position = set (position) piece board
> 
> 
> -- 2. and using the (:t ...) type definition abouve, none of these work
> 
> move :: Board -> Piece -> ((Field2 s t a b, Functor f) => (a -> f b) -> s -> f t) -> Board
> -- move :: Board -> Piece -> ((a -> f b) -> s -> f t) -> Board
> -- move :: Board -> Piece -> (a -> f b) -> Board
> -- move :: Board -> Piece -> (s -> f t) -> Board
> 
> move board piece position = set (position) piece board
> 
> -- 3. so the below code compiles, but doesn't do me much good... I need Position to be a lens, such that I can use A) set (position) piece board , instead of B) set (_2._1) 42 board
> 
> module Main where
> 
> import Control.Lens
> 
> data Piece = X | O | E deriving Show
> type Row = [Piece]
> type Board = [Row]
> data Position = Int Int deriving Show
> 
> move :: Board -> Piece -> Position -> Board
> move board piece position = board

You seem set on lenses. So if you write that move function like this (in case anyone’s wondering, I happen to know this isn’t a homework question):

data Piece = X | O | E deriving Show

move :: a -> b1 -> ASetter a b a1 b1 -> b
move board position piece = board & position .~ piece

This’ll work. But how are you going to get the position? If you’re given an integer based coordinate, as you seem to want from your definitions of Position, then you’re going to have to do something ugly.

Why not just go with an array and be done with it? Something like this (with your original definition of Piece):

import Data.Array

data Piece' = X | O | E deriving Show
type Position' = (Int,Int)
type Board' = Array Position’ Piece'

board' :: Board'
board' = array ((1,1),(3,3)) [((i,j), E) | i <- [1,2,3], j <- [1,2,3]]

move' :: Board' -> Piece' -> Position' -> Board'
move' board piece pos = board // [(pos, piece)]

If you want a slightly less ugly of looking at the board

import qualified Data.List.Split as S

pp board = mapM_ print $ S.chunksOf 3 $ elems board

will display the board something like:

[E,E,E]
[E,E,E]
[E,E,E]

I hope I didn’t say too much.

Cheers,
Bob

> 
> main :: IO ()
> main = putStrLn "Hello World"
> 
> 
> 
> Cheers mate :) 
> 
> Tim Washington 
> Interruptsoftware.com 
>  
> 
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners



More information about the Beginners mailing list