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:  Chessboard Module, opinions on? (i?fai)
   2.  Re: Chessboard Module, opinions on... (Christian Maeder)
   3.  Memoization (Shawn Willden)
   4. Re:  Memoization (Daniel Fischer)
   5. Re:  Chessboard Module, opinions on? (Andy Elvey)
   6. Re:  Chessboard Module, opinions on? (Andy Elvey)
   7.  list monad question (Matthias Guedemann)
   8. Re:  list monad question (David Virebayre)
   9. Re:  list monad question (Jan Jakubuv)


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

Message: 1
Date: Wed, 28 Oct 2009 11:23:31 -0400
From: i?fai <iae...@me.com>
Subject: Re: [Haskell-beginners] Chessboard Module, opinions on?
To: Darrin Thompson <darri...@gmail.com>
Cc: Beginners@haskell.org
Message-ID: <10bde766-a51e-44fd-903b-bc6c9085f...@me.com>
Content-Type: text/plain; charset=iso-8859-1; format=flowed; delsp=yes

If I had a clock, I would consider it :P

On 2009-10-28, at 11:20 AM, Darrin Thompson wrote:

> On Wed, Oct 28, 2009 at 2:33 AM, iæfai <iae...@me.com> wrote:
>> The chess AI process is something I still have to hunt for mind  
>> you, but the
>> part that is the most interesting is that I am going to be  
>> controlling a
>> $50,000 robot with this in class :P.
>>
>
> For $50k do you get a robot that can play a serious intimidating
> blitz? Can it smack the clock with Class A player _authority_? :-)
>
> --
> Darrin



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

Message: 2
Date: Wed, 28 Oct 2009 17:01:29 +0100
From: Christian Maeder <christian.mae...@dfki.de>
Subject: [Haskell-beginners] Re: Chessboard Module, opinions on...
To: i?fai <iae...@me.com>
Cc: Beginners@haskell.org
Message-ID: <4ae86ad9.6000...@dfki.de>
Content-Type: text/plain; charset=ISO-8859-1

iæfai schrieb:
> Andy, feel free. I should note that I am going to update this code to
> use Text.PrettyPrint.HughesPJ shortly. In addition, it will be

Using a pretty printer library for this fixed format seems unnecessary
to me.

C.


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

Message: 3
Date: Wed, 28 Oct 2009 19:45:35 -0600
From: Shawn Willden <shawn-hask...@willden.org>
Subject: [Haskell-beginners] Memoization
To: beginners@haskell.org
Message-ID: <200910281945.35769.shawn-hask...@willden.org>
Content-Type: text/plain;  charset="us-ascii"

Hi,

I've just begun experimenting with Haskell, and I'm having a lot of fun, but 
my first semi-serious program is in need of some optimization, and based on 
the results of profiling I think a really good start is to memoize one 
particular function which is called many, many times (and currently consumes 
over 80% of the program run time).

The function takes a two-dimensional range and a location within that range 
and returns a list of the locations vertically and horizontally adjacent to 
that location and within the bounds

type Bounds = ((Int,Int),(Int,Int))
type Location = (Int,Int)
adjacentCells :: Bounds -> Location -> [Location]
adjacentCells bounds (col, row) = filter valid cells
    where
      valid loc = inRange bounds loc
      neighborLoc' = [(col-1,row),(col+1,row),(col,row-1),(col,row+1)]

The ranges are fairly small -- certainly no more than 10x10, and each location 
has an associated list of at most 4 neighbors (edge locations have less).  
During a given run of the program, the bounds are fixed.

So, any tips on how I can memoize this function?  I have read the Memoization 
page on the wiki, and I understand (I think) the recursive memoization 
section, but it's not clear to me how to apply that approach.  Section one on 
non-recursive memoization seems like what I want, but I don't understand the 
section and the links provided haven't shed any light for me.

The section uses the following notation to describe how to construct a map to 
be used to hold the keys and values:

  Map ()            b  := b
  Map (Either a a') b  := (Map a b, Map a' b)
  Map (a,a')        b  := Map a (Map a' b)

but I'm not sure what that notation is.  It's not Haskell code, I don't think.

Any and all suggestions appreciated.

Thanks,

        Shawn.


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

Message: 4
Date: Thu, 29 Oct 2009 03:20:43 +0100
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Memoization
To: beginners@haskell.org
Message-ID: <200910290320.44286.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Donnerstag 29 Oktober 2009 02:45:35 schrieb Shawn Willden:
> Hi,
>
> I've just begun experimenting with Haskell, and I'm having a lot of fun,
> but my first semi-serious program is in need of some optimization, and
> based on the results of profiling I think a really good start is to memoize
> one particular function which is called many, many times (and currently
> consumes over 80% of the program run time).
>
> The function takes a two-dimensional range and a location within that range
> and returns a list of the locations vertically and horizontally adjacent to
> that location and within the bounds
>
> type Bounds = ((Int,Int),(Int,Int))
> type Location = (Int,Int)
> adjacentCells :: Bounds -> Location -> [Location]
> adjacentCells bounds (col, row) = filter valid cells
>     where
>       valid loc = inRange bounds loc
>       neighborLoc' = [(col-1,row),(col+1,row),(col,row-1),(col,row+1)]
>
> The ranges are fairly small -- certainly no more than 10x10, and each
> location has an associated list of at most 4 neighbors (edge locations have
> less). During a given run of the program, the bounds are fixed.

Probably the simplest thing to do is use an array.
At the start of your programme

let neighbourArray = array bounds [(loc, adjacentCells bounds loc) | loc <- 
range bounds]

and replace calls "adjacentCells bounds loc" with "neighbourArray!loc"


>
> Thanks,
>
>         Shawn.




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

Message: 5
Date: Thu, 29 Oct 2009 21:03:05 +1300
From: Andy Elvey <andy.el...@paradise.net.nz>
Subject: Re: [Haskell-beginners] Chessboard Module, opinions on?
To: i?fai <iae...@me.com>
Cc: Beginners@haskell.org
Message-ID: <4ae94c39.8060...@paradise.net.nz>
Content-Type: text/plain; charset=windows-1252; format=flowed


Great!   Many thanks.... :)   

 - Andy

iæfai wrote:
> Andy, feel free. I should note that I am going to update this code to 
> use Text.PrettyPrint.HughesPJ shortly. In addition, it will be 
> cabalizing it and  go up on hackage once I figure it out.
>
> I will keep you informed of this.
>
> - iæfai
>
> On 2009-10-28, at 4:23 AM, Andy Elvey wrote:
>
>> iæfai wrote:
>>>
>>> I have just recently finished a 'ChessBoard' module that is meant to 
>>> represent a chess board. I could use some opinions and/or 
>>> suggestions on the module.
>>>
>>> To give an example of how this can be used right now, and was my 
>>> immediate goal, you can do this:
>>>
>>> *ChessBoard> putStr $ cout defaultBoard
>>> +----+----+----+----+----+----+----+----+
>>> | RB | NB | BB | QB | KB | BB | NB | RB |
>>> +----+----+----+----+----+----+----+----+
>>> | PB | PB | PB | PB | PB | PB | PB | PB |
>>> +----+----+----+----+----+----+----+----+
>>> |    |    |    |    |    |    |    |    |
>>> +----+----+----+----+----+----+----+----+
>>> |    |    |    |    |    |    |    |    |
>>> +----+----+----+----+----+----+----+----+
>>> |    |    |    |    |    |    |    |    |
>>> +----+----+----+----+----+----+----+----+
>>> |    |    |    |    |    |    |    |    |
>>> +----+----+----+----+----+----+----+----+
>>> | PW | PW | PW | PW | PW | PW | PW | PW |
>>> +----+----+----+----+----+----+----+----+
>>> | RW | NW | BW | QW | KW | BW | NW | RW |
>>> +----+----+----+----+----+----+----+----+
>>>
>>> I have not determined exactly how I will be making moves, but the 
>>> logic will not be in my program. I am going to be using a chess 
>>> engine in another process (I haven't chosen a chess engine yet that 
>>> works on both windows and mac through stdin/stdout).
>>>
>>> The module itself follows, I appreciate any thoughts you might have.
>>>
>>>
>>> module ChessBoard where
>>>
>>> import Data.Sequence
>>> import Data.Foldable
>>> import Data.Maybe
>>> import Data.List as List
>>>
>>> class NiceLook a where
>>>    cout :: a -> String
>>>
>>>
>>> data Piece = Bishop | Rook | Knight | King | Queen | Pawn | NoPiece
>>>    deriving (Show, Eq)
>>>
>>> instance NiceLook Piece where
>>>        cout Bishop = "B"
>>>        cout Rook   = "R"
>>>        cout Knight = "N"
>>>        cout Queen  = "Q"
>>>        cout Pawn   = "P"
>>>        cout King   = "K"
>>>        cout _      = " "
>>>
>>> data Colour = Black | White | NoColour
>>>    deriving (Show, Eq)
>>>
>>> instance NiceLook Colour where
>>>        cout Black = "B"
>>>        cout White = "W"
>>>        cout NoColour = " "
>>>
>>>        -- error "..." might be useful
>>>
>>> data Square = Square Piece Colour
>>>    deriving (Show, Eq)
>>>
>>> instance NiceLook (Square) where
>>>        cout (Square p c) = (cout p) ++ (cout c)
>>>
>>> data Row = Row (Seq Square)
>>>    deriving (Show, Eq)
>>>
>>> instance NiceLook (Row) where
>>>        cout (Row s) = "|" ++ foldMap (\x -> " " ++ cout x ++ " |") 
>>> s       -- thnx Saizan
>>>
>>> makeRow n = case (List.length n) of
>>>                8 -> Row (fromList n)
>>>                _ -> error "Row is not 8 squares"
>>>
>>> makeColouredSquares n c = makeRow $ map makeSquare (zip n (replicate 
>>> 8 c))
>>>
>>> makeSquare (n,c) = Square n c
>>>
>>> pawns = [Pawn, Pawn, Pawn, Pawn, Pawn, Pawn, Pawn, Pawn]
>>> back = [Rook, Knight, Bishop, Queen, King, Bishop, Knight, Rook]
>>> blank = [NoPiece, NoPiece, NoPiece, NoPiece, NoPiece, NoPiece, 
>>> NoPiece, NoPiece]
>>>
>>> data Board = Board (Seq Row)
>>>    deriving (Show, Eq)
>>>
>>> instance NiceLook (Board) where
>>>    cout (Board c) = borderOutput ++ "\n" ++ (foldMap (\x -> cout x 
>>> ++ "\n" ++ borderOutput ++ "\n") c)
>>>
>>> defaultBoard = Board (makeColouredSquares back Black <|
>>>                      makeColouredSquares pawns Black <|
>>>                      makeColouredSquares blank NoColour <|
>>>                      makeColouredSquares blank NoColour <|
>>>                      makeColouredSquares blank NoColour <|
>>>                      makeColouredSquares blank NoColour <|
>>>                      makeColouredSquares pawns White <|
>>>                      makeColouredSquares back White <| empty)
>>>
>>>
>>> borderOutput = "+" ++ (List.foldr1 (++) $ replicate 8 "----+")
>>>
>>>
>> Hi iæfai! This is great!  Very nicely done!
>> I was just wondering - I potter around with crosstab code in several 
>> programming languages, and this (the table-creation code in 
>> particular) could be quite handy in that area.  So, would you mind if 
>> I used this?  I'll give credit of course! Many thanks for posting 
>> this neat bit of code! - Andy
>>
>> _______________________________________________
>> Beginners mailing list
>> Beginners@haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>
>



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

Message: 6
Date: Thu, 29 Oct 2009 21:04:12 +1300
From: Andy Elvey <andy.el...@paradise.net.nz>
Subject: Re: [Haskell-beginners] Chessboard Module, opinions on?
To: Christian Maeder <christian.mae...@dfki.de>
Cc: beginners <beginners@haskell.org>
Message-ID: <4ae94c7c.8000...@paradise.net.nz>
Content-Type: text/plain; charset=windows-1252; format=flowed

Hi Christian -

Thanks for that!  I'll check that out....  :) 
Bye for now  -
- Andy

Christian Maeder wrote:
> You may want to look at the tabular package for table-creation code:
> http://hackage.haskell.org/package/tabular
>
> C.
>
> Andy Elvey schrieb:
>   
>> Hi iæfai! This is great!  Very nicely done!
>> I was just wondering - I potter around with crosstab code in several
>> programming languages, and this (the table-creation code in particular)
>> could be quite handy in that area.  So, would you mind if I used this? 
>> I'll give credit of course! Many thanks for posting this neat bit of
>> code! - Andy
>>
>>     
>
>   



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

Message: 7
Date: Fri, 30 Oct 2009 12:44:41 +0100
From: Matthias Guedemann <matthias.guedem...@ovgu.de>
Subject: [Haskell-beginners] list monad question
To: beginners <beginners@haskell.org>
Message-ID: <1256902955-sup-...@pc44es141.cs.uni-magdeburg.de>
Content-Type: text/plain; charset=UTF-8


Hi,

a friend of mine wanted to write function (in Perl) that creates all tuples of
length 3 of the elements of a given list,
e.g. [(0,0,0),(0,0,1),(0,0,2),...,(5,5,5)] for the list [0..5]. Trying to get
better at Haskell, I wrote a small function using the list monad for this 
(tuples
replaced with lists)

all3 ls = do
  a <- ls
  b <- ls
  c <- ls
  return [a,b,c]

Now I want to make it capable to create all combinations of length n instead of
fixed length 3 (that's why list instead of tuple), but I don't really see how.
As the do notation translates to 

ls >>= \a ->  etc. 

I thought it should be possible to have some sort of "foldr (>>=)" over a list
of length n, but I can't figure out how to collect the variable number of
results in a list for the "return".

Any hints for that?

best regards
Matthias


-- 
__________________________________________________________
                                            ___  __    __
Dipl. Inf. Matthias Guedemann              / __\/ _\  /__\
Computer Systems in Engineering           / /   \ \  /_\
Otto-von-Guericke Universitaet Magdeburg / /___ _\ \//__
Tel.: 0391 / 67-19359                    \____/ \__/\__/
__________________________________________________________


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

Message: 8
Date: Fri, 30 Oct 2009 13:09:50 +0100
From: David Virebayre <dav.vire+hask...@gmail.com>
Subject: Re: [Haskell-beginners] list monad question
To: Matthias Guedemann <matthias.guedem...@ovgu.de>
Cc: beginners <beginners@haskell.org>
Message-ID:
        <4c88418c0910300509w4e949ce9y73f784a248960...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Fri, Oct 30, 2009 at 12:44 PM, Matthias Guedemann
<matthias.guedem...@ovgu.de> wrote:

> a friend of mine wanted to write function (in Perl) that creates all tuples of
> length 3 of the elements of a given list,
> e.g. [(0,0,0),(0,0,1),(0,0,2),...,(5,5,5)] for the list [0..5]. Trying to get
> better at Haskell, I wrote a small function using the list monad for this 
> (tuples
> replaced with lists)
>
> all3 ls = do
>  a <- ls
>  b <- ls
>  c <- ls
>  return [a,b,c]

Almost there :

all3 ls = do
  a <- ls
  b <- ls
  c <- ls
  return (a,b,c)

For each element a of list ls , for each element b of the same list
ls, and for each element c of the same list ls, make a tuple of them.
return the list of tall the tuples.

You could also write it with a list comprehension :

all3 ls = [ (a,b,c) | a <- ls, b <- ls, c <- ls ]

David.


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

Message: 9
Date: Fri, 30 Oct 2009 12:23:27 +0000
From: Jan Jakubuv <jaku...@gmail.com>
Subject: Re: [Haskell-beginners] list monad question
To: Matthias Guedemann <matthias.guedem...@ovgu.de>
Cc: beginners <beginners@haskell.org>
Message-ID: <20091030122327.ga11...@lxultra2.macs.hw.ac.uk>
Content-Type: text/plain; charset=us-ascii

Hi Matthias,

On Fri, Oct 30, 2009 at 12:44:41PM +0100, Matthias Guedemann wrote:
> 
> Hi,
> 
> a friend of mine wanted to write function (in Perl) that creates all tuples of
> length 3 of the elements of a given list...
> 
> all3 ls = do
>   a <- ls
>   b <- ls
>   c <- ls
>   return [a,b,c]
> 
> Now I want to make it capable to create all combinations of length n instead 
> of
> fixed length 3 (that's why list instead of tuple), but I don't really see how.

How about a recursive function like this:

    alln 1 ls = map (:[]) ls
    alln n ls = do
        a <- ls
        as <- alln (n-1) ls
        return (a:as)

Note that `ls :: [t]` and `all (n-1) ls :: [[t]]` has different types but
it's okay because both are in the list monad. 

Also, it can be done with list comprehensions:

    alln' 1 ls = [[a] | a<-ls] 
    alln' n ls = [a:as | a<-ls, as<-alln' (n-1) ls]

Sincerely,
    jan.



-- 
Heriot-Watt University is a Scottish charity
registered under charity number SC000278.



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

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


End of Beginners Digest, Vol 16, Issue 26
*****************************************

Reply via email to