[Haskell-beginners] Peer review of an attempt to solve the golf-tee puzzle?
Scott Thoman
scott at thoman.org
Thu Oct 6 02:25:23 CEST 2011
On Wed, Oct 5, 2011 at 1:44 PM, Brent Yorgey <byorgey at seas.upenn.edu> wrote:
> On Wed, Oct 05, 2011 at 11:02:24AM -0400, Scott Thoman wrote:
>> Hi,
>>
>> I'm looking to see of anyone is interested in a quick code review. I
>> coded a quick solution to the golf-tee puzzle (like you see a places
>> like Cracker Barrel, 15 piece triangle where you hop the pegs in order
>> to get down to one left). My solution seems to work, seems to perform
>> ok, and seems to come up with a very large number of distinct
>> solutions.
>>
>> I'm looking for some feedback as far as:
>> - am I "getting" it? :)
>> - is the approach general enough?
>> - does it look anything like idiomatic haskell?
>> - any places to make things simpler or more point-free-ish?
>> - any types are overkill, too restrictive (I added the Board type so
>> maybe it could be an instance of Show to display the triangle but
>> didn't go that far)
>
> Hi Scott,
>
> It seems like a nice general solution to me. It looks like it would
> also be applicable to a puzzle I remember from my childhood which had
> the same rules (jump one piece over another to remove the jumped
> piece, try to end up with only a single piece) but had a board with a
> starting configuration that looked like this:
>
> XXX
> XXX
> XXXXXXX
> XXX XXX
> XXXXXXX
> XXX
> XXX
>
> Some comments interspersed below.
>
>> -- | A module of functions around solving the "tee board" type
>> -- puzzles. The main example of this is the 15 piece puzzle
>> -- found at places like Cracker Barrel.
>> -- The board is modeled as an immutable array where indexes
>> -- are Ints and the elements are also Ints. The contents are
>> -- expected to be 0 for an empty spot and 1 for a full spot.
>
> Why use Int? Wouldn't Bool be more appropriate?
>
>> -- | Our representation of a board - an indexable array
>> -- of Ints (slots are 0 -> empty, 1 -> full).
>> newtype Board = Board (Array Int Int)
>> deriving (Show, Eq)
>> --type Board = Array Int Int
>
> You mentioned making a Show instance for Board to display the puzzle
> but I wouldn't do that. Show is intended to produce valid Haskell
> expressions, i.e. you should really only use the automatically derived
> Show instance. If you want to print out the board nicely I would just
> make a function displayBoard :: Board -> String.
>
>>
>> -- | Make board of the given size filled with the given value
>> populateBoard :: Int -> Int -> Board
>> populateBoard s v = board s $ map (\x -> (x, v)) $ range (1, s)
>>
>> -- | Make an empty board of the given size
>> emptyBoard :: Int -> Board
>> emptyBoard = (flip populateBoard) 0
>>
>> -- | Make a full board of the given size
>> fullBoard :: Int -> Board
>> fullBoard = (flip populateBoard) 1
>
> The fact that you had to use 'flip' to define emptyBoard and fullBoard
> suggests that the order of parameters to populateBoard should be switched.
>
>> -- | Test whether a move is valid on the given board.
>> isValidMove :: Board -> Move -> Bool
>> isValidMove b (s,j,e) = (b `atSpot` s == 1) && (b `atSpot` j == 1) && (b `atSpot` e == 0)
>
> If the board stored Bools you could just write (b `atSpot` s) && (b
> `atSpot` j) && (not (b `atSpot` e)).
>
>> -- | Simple foldl for our Board (array) that folds up the
>> -- values on the board.
>> -- (This one knows about the internal board implementation.)
>> foldBoard :: (Int -> Int -> Int) -> Int -> Board -> Int
>> foldBoard f a (Board b) =
>> let hi = snd $ bounds b
>> doit a i = if (i > hi) then
>> a
>> else
>> doit (f a (b ! i)) (i + 1)
>> in
>> doit a 1
>
> This is an ugly and fiddly way to fold over the values in the array.
> Instead, use the 'elems' function to get a list of the array elements
> and then do a fold over that.
>
>> -- | The specifics for the 15 piece "tee board" puzzle. This module
>> -- contains the details about valid moves, etc. on this board layout.
>> -- The board layout is labled like the following:
>> -- 01
>> -- 02 03
>> -- 04 05 06
>> -- 07 08 09 10
>> -- 11 12 13 14 15
>> module TriangleTeeBoard where
>> import TeeBoard
>> import Data.Array
>>
>> -- | The valid moves on the 15 piece triangle "tee board".
>> -- This is just a list of (start, jumped, end) tuples and can be
>> -- used when called TeeBoard.solutions.
>> validTriangleMoves :: [(Int, Int, Int)]
>> validTriangleMoves = [
>> (1,2,4),
>> (1,3,6),
>> (2,4,7),
>
> Ugh! I wonder if you could figure out a way to generate this list
> instead of just writing it down by hand. Although I realize that
> might be tricky. It might become easier if you choose a different
> representation for locations. For example you could represent a
> location as a triple (Int, Int, Int), representing the
> distances from the bottom, left, and right edges respectively. Like
> so:
>
> (4,0,0)
> (3,0,1) (3,1,0)
> (2,0,2) (2,1,1) (2,2,0)
>
> and so on. Notice that the sum of the values is constantly one less
> than the size of the puzzle. Then from any location you can easily
> compute the adjacent locations like so:
>
> (+1,-1,0) (+1,0,-1)
> (0,-1,+1) (i,j,k) (0,+1,-1)
> (-1,0,+1) (-1,+1,0)
>
> which should make generating valid moves a snap. Of course, it would
> be nice to still store the board in an array indexed by Int: to convert
> one of these triple-locations (i,j,k) to a unique integer index you can do
>
> locToIndex (i,j,k) = (4-i)*(4-i+1) `div` 2 + j
>
> Just a fun idea.
>
> -Brent
>
Brent,
Thank you very much for your comments. I didn't realize that Show was
for producing valid Haskell so that's good to know. I think I got
stuck on the board containing Ints since I was in the mindset of
folding the board mathematically but everything would be more clear
with Bools. I'll probably switch that and use 'elems' since I didn't
realize that existed. I'll be sad to see the array fold
implementation go :) but I'll rather use the standard fold.
I was talking with the guy who started this little challenge and our
conversations were heading in the "how do I auto-generate the valid
moves for various boards" direction. I think you may be onto
something with your suggestion - the data itself making the valid
moves easy to figure out. The valid moves list was tedious to write
down but it was worth it to prove the algorithm worked.
/stt
More information about the Beginners
mailing list