[Haskell-beginners] Dipping Toes Into Haskell

Timothy Washington twashing at gmail.com
Tue Mar 24 02:38:24 UTC 2015


Hey man...


On Mon, Mar 23, 2015 at 4:57 AM, Bob Hutchison <hutch-lists at recursive.ca>
wrote:

> Hi Tim,
>
> Straying from clojure? :-)
>
>
Lol, love it!! I'm a free spirit. Can't hold me down :)



> On Mar 22, 2015, at 12:33 PM, Timothy Washington <twashing at gmail.com>
> wrote:
>
> So I've finally had a chance to revisit my tictactoe game.
>
>
> import Control.Lens
>
> data Piece = X | O | E deriving Show
> type Row = [Piece]
> type Board = [Row]
> *data Position = Int Int deriving Show*
>
> -- put an X or O in a position
> *move :: Board -> Piece -> Position -> Board*
> move board piece position = board
>
> main :: IO ()
> main = putStrLn "Hello World"
>
> Now, if I want to make a move, I'll want to set a *piece* on a *position*,
> on a *board*. Let's assume the board has the following shape.
>
> λ> let r1 = (E,E,E)
> λ> let r2 = (E,E,E)
> λ> let r3 = (E,E,E)
> λ> let board = (r1,r2,r3)
> ((E,E,E),(E,E,E),(E,E,E))
>
>
> To return an updated board, I dug around and *i)* couldn't find a core
> Haskell equivalent to Clojure's update-in
> <http://clojuredocs.org/clojure.core/update-in>. *ii)* Zippers only deal
> with trees of left / right nodes. *iii)* So that left me with Control.Lens
> <https://github.com/ekmett/lens/wiki/Examples>. Now I can easily inspect
> and update the board like so.
>
>
> Or you could use an two dimensional array of Positions instead
> (Data.Array).
>

Hmm, probably. But the function's type signature below, seem to be the
first order of business, no?



> λ> board^*._**2._1*
> E
> λ> set (*_2._1*) 42 board
> ((E,E,E),(42,E,E),(E,E,E))
>
>
> I can then parameterize _2 or _1 like so.
>
> λ> let a = _2
> λ> board ^. a
> (E,E,E)
>
>
> You can probably find the type of _1, _2, _3 in the repl, and use that in
> your code below.
>

The types (:t ...) of both of these are:

   - a :: (Field2 s t a b, Functor f) => (a -> f b) -> s -> f t
   - _2 :: (Field2 s t a b, Functor f) => (a -> f b) -> s -> f t



> But I can't figure out how to include that parameter's type into a
> *Position* type definition. I've tried these unsuccessfully.
>
> *data Position = Int Int deriving Show  -- original type definition*
> *data Position = Simple Lens (Int a) (Int a) deriving Show  -- failing try
> 1*
>
>
> These are very suspicious. Did you intend to define constructors ‘Int’ and
> ‘Simple’? Maybe you meant something like:
>
> data Position = Position Int Int deriving Show
>
> In which case you’ll have a type called ‘Position’ and a constructor with
> the same name.
>
> Cheers,
> Bob
>
>
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

main :: IO ()
main = putStrLn "Hello World"




Cheers mate :)

Tim Washington
Interruptsoftware.com <http://interruptsoftware.com/>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/beginners/attachments/20150323/13089df0/attachment-0001.html>


More information about the Beginners mailing list