Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Learning about channels (Benjamin Edwards)
   2.  Simple Chess Program for Learning FP (Jordan Cooper)
   3. Re:  Simple Chess Program for Learning FP (Daniel Fischer)
   4. Re:  Simple Chess Program for Learning FP (Yitzchak Gale)
   5. Re:  Simple Chess Program for Learning FP (Jordan Cooper)
   6. Re:  Simple Chess Program for Learning FP (Brent Yorgey)


----------------------------------------------------------------------

Message: 1
Date: Mon, 31 May 2010 22:24:45 +0200
From: Benjamin Edwards <edwards.b...@gmail.com>
Subject: Re: [Haskell-beginners] Learning about channels
To: "Dean Herington & Elizabeth Lacey" <heringtonla...@mindspring.com>
Cc: beginners@haskell.org
Message-ID:
        <aanlktik4xk1alnpcqrtwf1al8-qhbxiahz7mlsgv5...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

That's a really good idea. Thanks for the insight :)

On 31 May 2010 19:33, Dean Herington & Elizabeth Lacey <
heringtonla...@mindspring.com> wrote:

> At 10:06 AM +0100 5/25/10, Benjamin Edwards wrote:
>
>> NB: This was posted in fa.haskell  first, I guess it was the wrong forum
>> for this kind of question as it was left unanswered :)
>>
>> Hi,
>>
>> I'm having a few issues getting some toy programs to work whilst I try
>> to get a better understanding of how to model processes and channels.
>> I am just trying to use the real base blocks and failing miserably.
>> Here is an example (yes this is utterly contrived and sill, but I lack
>> imagination... sue me):
>>
>> I want my main thread to do the following:
>>
>> 1. make a channel
>> 2. spawn a thread (producer) that will write a series of lists of
>> integers to the the channel, then exit.
>> 3. spawn another thread that will read from the channel and sum all of
>> the input. It should exit when both the channel is empty and and the
>> producer thread has finished writing to it.
>> 4. Main thread should print the sum.
>>
>> My current code should uses a trick I have seen else where which is to
>> have the result of "task" running in the thread put into an MVar. So
>> my condition for the reading thread exiting is to check if the MVar of
>> the producer thread is not empty and if the channel is empty. If those
>> two things are true, exit the thread. Unfortunately if somehow seems
>> able to to get to a stage where the produce thread has finished and
>> the channel is empty, but is blocking on a read.
>>
>> I have the following code, but it always blocks indefinitely on a
>> read. I am sure there is something obviously deficient with it, but I
>> can't work out what it is. Any help would be greatly appreciated. Of
>> course, if I'm doing it all wrong, please tell me that too :)
>>
>> module Main
>>  where
>>
>> import Control.Concurrent
>> import Control.Concurrent.STM
>> import Control.Monad (forever)
>> import Data.Map as M
>>
>> main :: IO ()
>> main = do oc <- newChan
>>          counter <- newTVarIO (0 :: Integer)
>>          p <- forkJoin $ produce oc [1..1000]
>>          c <- forkJoin $ loop oc p counter
>>          takeMVar c >>= print
>>
>> produce :: Chan [Integer] -> [Integer] -> IO ()
>> produce ch [] = return ()
>> produce ch xs = do let (hs,ts) = splitAt 100 xs
>>                   writeChan ch hs
>>                   produce ch ts
>>
>> loop :: Chan [Integer] -> MVar () -> TVar Integer -> IO Integer
>> loop ch p n = do f <- isEmptyMVar p
>>                 e <- isEmptyChan ch
>>                 if e && (not f)
>>                   then atomically (readTVar n)
>>                   else do xs <- readChan ch
>>                           atomically $ do x <- readTVar n
>>                                           writeTVar n (x + sum xs)
>>                           loop ch p n
>>
>> forkJoin :: IO a -> IO (MVar a)
>> forkJoin task = do mv <- newEmptyMVar
>>                   forkIO (task >>= putMVar mv)
>>                   return mv
>>
>
>
> By encoding end-of-data directly in the channel contents, you can simplify
> the code (and make it less prone to hangs such as the one you experienced.)
>  I've shown one way to do this below.  I've also made the accumulating count
> a simple parameter to the consumer function.  (Because the count is private
> to the consumer until it's passed to the main routine via the consumer's
> termination MVar, there's no need for additional inter-thread
> synchronization.)
>
> Dean
>
>
>
> module Main where
>
> import Control.Concurrent
>
> main :: IO ()
> main = do oc <- newChan
>          p <- forkJoin $ produce oc [1..1000]
>          c <- forkJoin $ consume oc 0
>          takeMVar c >>= print
>
> produce :: Chan (Maybe [Integer]) -> [Integer] -> IO ()
> produce ch [] = writeChan ch Nothing
>
> produce ch xs = do let (hs,ts) = splitAt 100 xs
>                   writeChan ch (Just hs)
>                   produce ch ts
>
> consume :: Chan (Maybe [Integer]) -> Integer -> IO Integer
> consume ch cnt = do mbInts <- readChan ch
>                    case mbInts of Just xs -> consume ch (cnt + sum xs)
>                                   Nothing -> return cnt
>
>
> forkJoin :: IO a -> IO (MVar a)
> forkJoin task = do mv <- newEmptyMVar
>                   forkIO (task >>= putMVar mv)
>                   return mv
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100601/79083e93/attachment-0001.html

------------------------------

Message: 2
Date: Tue, 1 Jun 2010 11:01:48 -0700
From: Jordan Cooper <nefi...@gmail.com>
Subject: [Haskell-beginners] Simple Chess Program for Learning FP
To: beginners <beginners@haskell.org>
Message-ID:
        <aanlktilybtfdvcclq1l-eqafokuchecozragaoffv...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

FP newbie here,

I'd like to start learning how to program more purely. Immutability is
something that tends to confuse me when it comes to handling state,
and I figure the only way I'll understand is if I do it myself.

In the past I coded a little chess game in C, where two computers
played each other (not well, but they made legal moves). I figured
this might be good to try and accomplish the same thing in Haskell.

Any general advice before I embark would be appreciated, though my
main question has to do with data structures. In C I used a
two-dimensional array to represent the board (I realize there are more
efficient representations, but I'm aiming for understanding over
performance). I'm not sure what the natural functional equivalent
would be, seeing as how arrays are immutable.

Tips appreciated!

Thanks,
J


------------------------------

Message: 3
Date: Tue, 1 Jun 2010 21:04:21 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Simple Chess Program for Learning FP
To: beginners@haskell.org
Message-ID: <201006012104.21981.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

On Tuesday 01 June 2010 20:01:48, Jordan Cooper wrote:
> FP newbie here,
>
> I'd like to start learning how to program more purely. Immutability is
> something that tends to confuse me when it comes to handling state,
> and I figure the only way I'll understand is if I do it myself.

If you don't want to pass the state around explicitly (and that gets 
tiresome rather soon), you can hide it from view using a State monad. 
Depending on what you do, that could be either the simple

Control.Monad.State[.Strict].State

or, if you need the functionality of other monads,

Control.Monad.State[.Strict].StateT

Using monad transformers (generally, types ending with a capital T) is, 
however, often less than obvious to beginners, so it might be a good idea 
to not dive in at the deep end, but rather to acclimatise oneself in the 
shallower waters first.
A good way to get used to State is writing yet another parser combinator 
library (look e.g. at the API docs for parsec to see what combinators to 
implement -- you don't need to write them all, you'll learn how to use 
State before that).

>
> In the past I coded a little chess game in C, where two computers
> played each other (not well, but they made legal moves). I figured
> this might be good to try and accomplish the same thing in Haskell.
>
> Any general advice before I embark would be appreciated, though my
> main question has to do with data structures. In C I used a
> two-dimensional array to represent the board (I realize there are more
> efficient representations, but I'm aiming for understanding over
> performance).

If performance isn't important, you can also use a two-dimensional array
(Data.Array; Array (Int,Int) (Maybe Piece) for example) in Haskell.
Actually, immutable arrays in Haskell are surprisingly snappy (at least if 
you compile with optimisations).

Another option is using Data.Map and representing the gamestate as a Map 
from positions to pieces.

> I'm not sure what the natural functional equivalent
> would be, seeing as how arrays are immutable.

There are also mutable arrays,
Data.Array.ST
and
Data.Array.IO
with the common interface
Data.Array.MArray

If you use STUArrays or IOUArrays, you can get very fast code, but it's 
better to come to close terms with declarative functional programming 
before learning how to write "almost C" in Haskell (your "almost C" will 
look far less ugly then).

>
> Tips appreciated!

Hmm,

you'll probably need

-- GameState : whose turn, which piece where
-- Move : which piece, from where, to which square

evaluatePosition :: GameState -> Value
-- Value could be Int or something else as long as it's comparable
-- this is the really hard part

chooseMove :: GameState -> Move
-- for all legal moves, evaluate the position if that move were made
-- choose the most promising one
-- if you try to implement an elaborate strategy, that'll be hard too,
-- you'll need to figure out which branches to cut off early and when
-- to stop looking further
-- You'll probably want to add a pseudo-random generator to choose
-- a move when there's no clear favourite

makeMove :: Move -> GameState -> GameState
   

>
> Thanks,
> J


------------------------------

Message: 4
Date: Tue, 1 Jun 2010 22:37:26 +0300
From: Yitzchak Gale <g...@sefer.org>
Subject: Re: [Haskell-beginners] Simple Chess Program for Learning FP
To: Daniel Fischer <daniel.is.fisc...@web.de>
Cc: beginners@haskell.org
Message-ID:
        <aanlktim2bz7zlnr7mzor7dvm7ye9iztxde3jbsocw...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Daniel Fischer wrote:
> If performance isn't important, you can also use a two-dimensional array
> (Data.Array; Array (Int,Int) (Maybe Piece) for example) in Haskell.
> Actually, immutable arrays in Haskell are surprisingly snappy (at least if
> you compile with optimisations).
> Another option is using Data.Map and representing the gamestate as a Map
> from positions to pieces.
> There are also mutable arrays,

A chess board is only 8x8, so depending on your algorithms,
a simple 2 dimensional list might be the fastest:

[[Maybe Piece]]

That also allows you to write simple, beautiful functional code, using
the wide selection of list functions available in the Prelude
and Data.List.

If you choose a map from positions to pieces, it might turn out
to be just about as fast to use a simple association list

[(Int, Int), Maybe Piece]

instead of all the machinery of Data.Map.Map (Int, Int) (Maybe Piece)
A chess board has only 64 locations.

Regards,
Yitz

Regards,
Yitz


------------------------------

Message: 5
Date: Tue, 1 Jun 2010 13:54:38 -0700
From: Jordan Cooper <nefi...@gmail.com>
Subject: Re: [Haskell-beginners] Simple Chess Program for Learning FP
To: g...@sefer.org
Cc: beginners <beginners@haskell.org>
Message-ID:
        <aanlktilltgash8wgmzoob5qmofmd_xt45hnoa833q...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On 6/1/10, Yitzchak Gale <g...@sefer.org> wrote:
> Daniel Fischer wrote:
>> If performance isn't important, you can also use a two-dimensional array
>> (Data.Array; Array (Int,Int) (Maybe Piece) for example) in Haskell.
>> Actually, immutable arrays in Haskell are surprisingly snappy (at least if
>> you compile with optimisations).
>> Another option is using Data.Map and representing the gamestate as a Map
>> from positions to pieces.
>> There are also mutable arrays,
>
> A chess board is only 8x8, so depending on your algorithms,
> a simple 2 dimensional list might be the fastest:
>
> [[Maybe Piece]]
>
> That also allows you to write simple, beautiful functional code, using
> the wide selection of list functions available in the Prelude
> and Data.List.
>
> If you choose a map from positions to pieces, it might turn out
> to be just about as fast to use a simple association list
>
> [(Int, Int), Maybe Piece]
>
> instead of all the machinery of Data.Map.Map (Int, Int) (Maybe Piece)
> A chess board has only 64 locations.
>
> Regards,
> Yitz
>
> Regards,
> Yitz
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>

Thank you, Daniel and Yitzchak! I think that will be enough to get me
started. As a general question, at what number of elements does it
become impractical to use Lists?


------------------------------

Message: 6
Date: Tue, 1 Jun 2010 17:00:47 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Simple Chess Program for Learning FP
To: beginners@haskell.org
Message-ID: <20100601210047.ga23...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Tue, Jun 01, 2010 at 01:54:38PM -0700, Jordan Cooper wrote:
> 
> Thank you, Daniel and Yitzchak! I think that will be enough to get me
> started. As a general question, at what number of elements does it
> become impractical to use Lists?

It's really not a question of number of elements, but of how you use
the lists.  If you are doing stream-processing sorts of things, you
can even idiomatically and efficiently use lists that are infinitely
long!  What lists are not good for is things where you need to do lots
of indexing, since indexing into a list requires first traversing the
beginning of the list.  However for small lists like 8-element lists,
it really doesn't make much of a difference.  You might now ask: well,
suppose I need to do indexing; at what number of elements does it
become impractical to use lists?  The answer is: it depends, probably
somewhere between 10 and 1 million.  Use lists, and if it's too slow,
you can switch later.

-Brent


------------------------------

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


End of Beginners Digest, Vol 24, Issue 2
****************************************

Reply via email to