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.  number formatting with locale (Dmitry Simonchik)
   2.  idiomatic haskell question (Tom Doris)
   3.  qtHaskell, ForeignPtr (Michael Mossey)
   4.  oops (Michael Mossey)
   5. Re:  oops (Peter Verswyvelen)
   6. Re:  qtHaskell, ForeignPtr (Daniel Fischer)
   7. Re:  idiomatic haskell question (Andrew Wagner)


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

Message: 1
Date: Mon, 7 Sep 2009 13:05:39 +0400
From: Dmitry Simonchik <d...@simonchik.net>
Subject: [Haskell-beginners] number formatting with locale
To: beginners@haskell.org
Message-ID:
        <80eb7b2e0909070205t649e6c01y648ae9756a42e...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi all haskell lovers

I'm trying to print out Double in russian locale (we use "," as decimal
separator insetad of "."). I'm trying to set locale with
System.Locale.SetLocale like

setLocale LC_ALL $ Just "ru_RU.UTF-8"

this returns Just "ru_RU.UTF-8", so it seems that function call succeeded,
but when I call

show 20.2

it just prints 20.2 and not desired 20,2

Can anyone please help?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090907/edd802be/attachment-0001.html

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

Message: 2
Date: Mon, 7 Sep 2009 18:28:22 +0100
From: Tom Doris <tomdo...@gmail.com>
Subject: [Haskell-beginners] idiomatic haskell question
To: beginners@haskell.org
Message-ID:
        <19e5d1d00909071028s349a7552tae8036f3b1567...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi all, I've recently started using Haskell and am looking for some feedback
on code I've written; I sometimes feel that maybe I'm not doing things the
best way possible that Haskell allows, and maybe missing out on obvious
improvements in brevity or elegance. So here's a tic-tac-toe solver I wrote
that does basic min-max search of the entire tree (not efficient
algorithmically, but it's tictactoe so a blank board can be fully solved in
a few seconds). Also, if people have suggestions on how to change the
program to actually output the moves it would make, please let me know -
right now it just responds with 1 for a win for X, 0 for a draw, and -1 for
a win for O. And there are probably bugs!
Thanks in advance

import Data.List
data Box = Blank | X | O deriving (Eq, Show)
-- usage: call score with the board rows concatenated: score [Blank, Blank,
Blank, Blank, Blank, Blank, Blank, Blank, Blank]
--  or      score [Blank, X, O, Blank, X, O, Blank, Blank, Blank]
-- score is 1 if X wins, 0 for draw, -1 for lose

score :: [Box] -> Int
score g  | haveline X g = 1
         | haveline O g = -1
         | gridfull g = 0
         | isxmove g = maximum (map score (makeallmoves X g))
         | otherwise = minimum (map score (makeallmoves O g))

tolines :: [Box] -> [[Box]]
tolines [a1, a2, a3, b1, b2, b3, c1, c2, c3] = [ [a1,a2,a3], [b1,b2,b3],
[c1,c2,c3],
                                              [a1,b1,c1], [a2,b2,c2],
[a3,b3,c3],
                                              [a1,b2,c3], [a3,b2,c1] ]

haveline ::  Box->[Box] -> Bool
haveline b g = any ([b,b,b]==) (tolines g)

gridfull :: [Box] -> Bool
gridfull g = not $ any  (Blank==) g

isxmove :: [Box] -> Bool
isxmove g = let movecount =  sum $ map (\b -> if b==Blank then 0 else 1) g
            in mod movecount 2 == 0

isomove = not . isxmove

fl :: Box->[Box]->[Box]->[[Box]]
fl b xs (Blank:ys) = [xs ++ b:ys]
fl _ _ _ = []

makeallmoves :: Box->[Box]-> [[Box]]
makeallmoves b g = concat $ zipWith (fl b) (inits g) (tails g)
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090907/9a7ec5f1/attachment-0001.html

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

Message: 3
Date: Mon, 7 Sep 2009 14:54:17 -0700 (PDT)
From: "Michael Mossey" <m...@alumni.caltech.edu>
Subject: [Haskell-beginners] qtHaskell, ForeignPtr
To: beginners@haskell.org
Message-ID:
        <64711.208.57.251.240.1252360457.squir...@mail.alumni.caltech.edu>
Content-Type: text/plain;charset=iso-8859-1

I'm trying to learn qtHaskell, an interface to the Qt GUI library. I am
fairly new to Haskell, but have used Qt for a long time, so I thought I
could probably reasonably attempt to grok qtHaskell at this point.

My main question is: anyone recommended a good explanation of the foreign
function or foreign pointer interface?

My immediate question is that I was poking through the Qtc docs, and saw
this:


Documentation

   data Object a

Constructors

   QObject !(ForeignPtr a)

I am not sure how Haddock works. Is this telling me that an Object
constructor takes one argument, which is of type QObject, where QObject is
a type constructor that takes !(ForeignPtr a)? Or is this saying it takes
two arguments, a QObject and a !(ForeignPtr a). That latter makes more
sense I guess. What does the ! mean?

Thanks,
Mike



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

Message: 4
Date: Mon, 7 Sep 2009 14:57:20 -0700 (PDT)
From: "Michael Mossey" <m...@alumni.caltech.edu>
Subject: [Haskell-beginners] oops
To: beginners@haskell.org
Message-ID:
        <53031.208.57.251.240.1252360640.squir...@mail.alumni.caltech.edu>
Content-Type: text/plain;charset=iso-8859-1

I'm sorry, I just noticed one of my prior questions was pretty silly. The
second Object is the name of the type constructor. I realized that now. I
was just fooled by the layout of Haddock and got temporarily confused.
However, I'm still interested in learning more about what the ! means, and
where I can learn about ForeignPtr (maybe a short tutorial to start).

Thanks,
Mike



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

Message: 5
Date: Tue, 8 Sep 2009 00:14:28 +0200
From: Peter Verswyvelen <bugf...@gmail.com>
Subject: Re: [Haskell-beginners] oops
To: Michael Mossey <m...@alumni.caltech.edu>
Cc: beginners@haskell.org
Message-ID:
        <a88790d10909071514i88fc884m2c8e59aa36e46...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

About the !

These might help

http://en.wikibooks.org/wiki/Haskell/Laziness
http://en.wikibooks.org/wiki/Haskell/Graph_reduction



On Mon, Sep 7, 2009 at 11:57 PM, Michael Mossey<m...@alumni.caltech.edu> wrote:
> I'm sorry, I just noticed one of my prior questions was pretty silly. The
> second Object is the name of the type constructor. I realized that now. I
> was just fooled by the layout of Haddock and got temporarily confused.
> However, I'm still interested in learning more about what the ! means, and
> where I can learn about ForeignPtr (maybe a short tutorial to start).
>
> Thanks,
> Mike
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>


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

Message: 6
Date: Tue, 8 Sep 2009 00:36:00 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] qtHaskell, ForeignPtr
To: beginners@haskell.org
Message-ID: <200909080036.00611.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Montag 07 September 2009 23:54:17 schrieb Michael Mossey:
> I'm trying to learn qtHaskell, an interface to the Qt GUI library. I am
> fairly new to Haskell, but have used Qt for a long time, so I thought I
> could probably reasonably attempt to grok qtHaskell at this point.
>
> My main question is: anyone recommended a good explanation of the foreign
> function or foreign pointer interface?
>
> My immediate question is that I was poking through the Qtc docs, and saw
> this:
>
>
> Documentation
>
>    data Object a
>
> Constructors
>
>    QObject !(ForeignPtr a)
>
> I am not sure how Haddock works. Is this telling me that an Object
> constructor takes one argument, which is of type QObject, where QObject is
> a type constructor that takes !(ForeignPtr a)? Or is this saying it takes
> two arguments, a QObject and a !(ForeignPtr a). That latter makes more
> sense I guess. What does the ! mean?

It tells you that the (Object a) datatype has a data-constructor called QObject 
(I know 
you already figured that out) which takes one argument of type (ForeignPtr a).
However, the constructor's argument type has a bang (!), which means that the 
constructor 
is strict in its argument.

For nonstrict constructors (data Ob a = Con a), you can happily create a value

Con _|_

which will be a nice and harmless citizen until you try to look at its 
contents. For 
example,

let x = Con undefined in x `seq` 3

returns 3, only

let x = Con undefined in 
     case x of 
       Con y -> y `seq` 3

will raise an exception.
If you make your constructor strict (data Thing a = SCon !a), it doesn't accept 
a bottom, 
the strict constructor evaluates its argument to weak head normal form, if it 
encounters a 
bottom, an exception is raised.
So,
Con _|_ /= _|_
but
SCon _|_ == _|_
>
> Thanks,
> Mike




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

Message: 7
Date: Mon, 7 Sep 2009 19:44:03 -0400
From: Andrew Wagner <wagner.and...@gmail.com>
Subject: Re: [Haskell-beginners] idiomatic haskell question
To: Tom Doris <tomdo...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <b8a8636e0909071644s2034a87er9ccdbba9871fd...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

First of all, I highly recommend reading John Hughes' paper "Why Functional
Programming Matters" (http://www.cs.chalmers.se/~rjmh/Papers/whyfp.pdf) to
get a grasp of how to write alpha-beta and similar algorithms functionally.
Secondly, I've been playing around lately with representing tree traversals
as operations on a zipper. That is:

type TreeTraversal a = State (TreeLoc a)

This would allow you to cleanly write a traversal function which would
"return" a score, but also have, as its state, a focus on the node which it
has selected, from which you could easily get a path. See some of the top
results at http://www.google.com/search?q=haskell+zipper for a refresher on
zippers if needed. I hope to release a library around this code some day
soon.

On Mon, Sep 7, 2009 at 1:28 PM, Tom Doris <tomdo...@gmail.com> wrote:

> Hi all, I've recently started using Haskell and am looking for some
> feedback on code I've written; I sometimes feel that maybe I'm not doing
> things the best way possible that Haskell allows, and maybe missing out on
> obvious improvements in brevity or elegance. So here's a tic-tac-toe solver
> I wrote that does basic min-max search of the entire tree (not efficient
> algorithmically, but it's tictactoe so a blank board can be fully solved in
> a few seconds). Also, if people have suggestions on how to change the
> program to actually output the moves it would make, please let me know -
> right now it just responds with 1 for a win for X, 0 for a draw, and -1 for
> a win for O. And there are probably bugs!
> Thanks in advance
>
> import Data.List
> data Box = Blank | X | O deriving (Eq, Show)
> -- usage: call score with the board rows concatenated: score [Blank, Blank,
> Blank, Blank, Blank, Blank, Blank, Blank, Blank]
> --  or      score [Blank, X, O, Blank, X, O, Blank, Blank, Blank]
> -- score is 1 if X wins, 0 for draw, -1 for lose
>
> score :: [Box] -> Int
> score g  | haveline X g = 1
>          | haveline O g = -1
>          | gridfull g = 0
>          | isxmove g = maximum (map score (makeallmoves X g))
>          | otherwise = minimum (map score (makeallmoves O g))
>
> tolines :: [Box] -> [[Box]]
> tolines [a1, a2, a3, b1, b2, b3, c1, c2, c3] = [ [a1,a2,a3], [b1,b2,b3],
> [c1,c2,c3],
>                                               [a1,b1,c1], [a2,b2,c2],
> [a3,b3,c3],
>                                               [a1,b2,c3], [a3,b2,c1] ]
>
> haveline ::  Box->[Box] -> Bool
> haveline b g = any ([b,b,b]==) (tolines g)
>
> gridfull :: [Box] -> Bool
> gridfull g = not $ any  (Blank==) g
>
> isxmove :: [Box] -> Bool
> isxmove g = let movecount =  sum $ map (\b -> if b==Blank then 0 else 1) g
>             in mod movecount 2 == 0
>
> isomove = not . isxmove
>
> fl :: Box->[Box]->[Box]->[[Box]]
> fl b xs (Blank:ys) = [xs ++ b:ys]
> fl _ _ _ = []
>
> makeallmoves :: Box->[Box]-> [[Box]]
> makeallmoves b g = concat $ zipWith (fl b) (inits g) (tails g)
>
>
>
>
>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090907/7be5e917/attachment.html

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

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


End of Beginners Digest, Vol 15, Issue 5
****************************************

Reply via email to