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:  A Quantity Type - Integer without the        Negative #'s
      (aditya siram)
   2. Re:  A Quantity Type - Integer without the Negative       #'s
      (Daniel Carrera)
   3. Re:  SQL Lexer (Keith Sheppard)
   4. Re:  A Quantity Type - Integer without the Negative       #'s
      (Magnus Therning)
   5.  Performance of function defined in a 'where'     clause
      (Kevin Haines)
   6. Re:  Performance of function defined in a 'where' clause
      (Brent Yorgey)
   7. Re:  SQL Lexer (Andy Elvey)
   8. Re:  Performance of function defined in a 'where'         clause
      (Peter Verswyvelen)


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

Message: 1
Date: Sat, 9 May 2009 02:07:10 -0500
From: aditya siram <aditya.si...@gmail.com>
Subject: Re: [Haskell-beginners] A Quantity Type - Integer without the
        Negative #'s
To: Magnus Therning <mag...@therning.org>
Cc: beginners@haskell.org
Message-ID:
        <594f78210905090007v7381e280q430f609823e57...@mail.gmail.com>
Content-Type: text/plain; charset="iso-2022-jp"

Cool, that's really interesting! So is it accurate to say "predicated"
datatypes [1] such as Int and String are provided by Haskell but you cannot
create them or specialize on a subset of them? And there are really only two
types of datatypes, tags [2] and the "predicated" types. Compound datatypes
are just a combination of the two.

-deech


[1] By predicated I mean a datatype that would actually cause a compiler
error ( not a runtime error ) if a method returned an out-of-bounds value.
[2] By  tags I mean the data constructors, but I find it easier to think of
them as tags because they can appear alone, eg. data Coins = Penny | Nickel
| Dime | Quarter
where nothing is being constructed.

On Fri, May 8, 2009 at 5:06 PM, Magnus Therning <mag...@therning.org> wrote:

> aditya siram wrote:
>
>> Hi all,
>> Is there a datatype in Haskell that can be used to represent only
>> quantities >= 0?  I got bitten by a bug because I forgot to reject an amount
>> that was below zero after applying a decrementing operator. A simple unit
>> test would have caught this, but I was wondering if there was some way of
>> getting the type system to ensure this.
>>
>
> Maybe Word32 (or one of it's siblings) would do?  It's basically the same
> as 'unsigned int' in C, so it can under- and over-flow.
>
> /M
>
> --
> Magnus Therning                        (OpenPGP: 0xAB4DFBA4)
> magnus$B!w(Btherning$B!%(Borg          Jabber: 
> magnus$B!w(Btherning$B!%(Borg
> http://therning.org/magnus         identi.ca|twitter: magthe
>
>
> _______________________________________________
> 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/20090509/1c242a87/attachment-0001.htm

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

Message: 2
Date: Sat, 09 May 2009 09:37:53 +0200
From: Daniel Carrera <daniel.carr...@theingots.org>
Subject: Re: [Haskell-beginners] A Quantity Type - Integer without the
        Negative        #'s
To: beginners <beginners@haskell.org>
Message-ID: <4a0532d1.9030...@theingots.org>
Content-Type: text/plain; charset=UTF-8; format=flowed

Magnus Therning wrote:
> aditya siram wrote:
>> Hi all,
>> Is there a datatype in Haskell that can be used to represent only 
>> quantities >= 0?  I got bitten by a bug because I forgot to reject an 
>> amount that was below zero after applying a decrementing operator. A 
>> simple unit test would have caught this, but I was wondering if there 
>> was some way of getting the type system to ensure this.
> 
> Maybe Word32 (or one of it's siblings) would do?  It's basically the 
> same as 'unsigned int' in C, so it can under- and over-flow.

What's under-flow?


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

Message: 3
Date: Sat, 9 May 2009 08:56:56 -0400
From: Keith Sheppard <keiths...@gmail.com>
Subject: Re: [Haskell-beginners] SQL Lexer
To: Patrick LeBoutillier <patrick.leboutill...@gmail.com>,
        beginners@haskell.org
Message-ID:
        <92e42b740905090556g4644f7ax71389bad2c0e6...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

This may be a better approach then my code. I didn't create a separate
parser/lexer.

-Keith

On Fri, May 8, 2009 at 9:53 PM, Patrick LeBoutillier
<patrick.leboutill...@gmail.com> wrote:
> Hi all,
>
> In the process of writing an SQL parser I started by writing a lexer.
> The code can be found here:
> http://hpaste.org/fastcgi/hpaste.fcgi/view?id=4736#a4736
>
> You can run it like this in ghci:
>
> Prelude SQL.Lexer> runLexer "select * from TABLE order by FIELD"
> [Token Reserved "select",Token Space " ",Token Operator "*",Token
> Space " ",Token Reserved "from",Token Space " ",Token Identifier
> "TABLE",Token Space " ",Token Reserved "order",Token Space " ",Token
> Reserved "by",Token Space " ",Token Identifier "FIELD"]
>
> Since this is pretty much my first Haskell project over 10 lines long,
> I'm looking for some feedback of any kind.
> Ultimately I would like to use this lexer to build a functional SQL
> parser using Parsec.
>
>
> Thanks,
>
> Patrick
>
> --
> =====================
> Patrick LeBoutillier
> Rosemère, Québec, Canada
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>


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

Message: 4
Date: Sat, 09 May 2009 17:30:02 +0100
From: Magnus Therning <mag...@therning.org>
Subject: Re: [Haskell-beginners] A Quantity Type - Integer without the
        Negative        #'s
To: beginners@haskell.org
Message-ID: <4a05af8a.9060...@therning.org>
Content-Type: text/plain; charset="utf-8"

Daniel Carrera wrote:
> Magnus Therning wrote:
>> aditya siram wrote:
>>> Hi all,
>>> Is there a datatype in Haskell that can be used to represent only 
>>> quantities >= 0?  I got bitten by a bug because I forgot to reject an 
>>> amount that was below zero after applying a decrementing operator. A 
>>> simple unit test would have caught this, but I was wondering if there 
>>> was some way of getting the type system to ensure this.
>>
>> Maybe Word32 (or one of it's siblings) would do?  It's basically the 
>> same as 'unsigned int' in C, so it can under- and over-flow.
> 
> What's under-flow?

Negative overflow:

   > let one = 1 :: Word8
   > one - 2
   255

/M

-- 
Magnus Therning                        (OpenPGP: 0xAB4DFBA4)
magnus@therning.org          Jabber: magnus@therning.org
http://therning.org/magnus         identi.ca|twitter: magthe

-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 197 bytes
Desc: OpenPGP digital signature
Url : 
http://www.haskell.org/pipermail/beginners/attachments/20090509/2dd40e5a/signature-0001.bin

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

Message: 5
Date: Sat, 09 May 2009 17:50:33 +0100
From: Kevin Haines <kevin.hai...@ntlworld.com>
Subject: [Haskell-beginners] Performance of function defined in a
        'where' clause
To: beginners@haskell.org
Message-ID: <4a05b459.3070...@ntlworld.com>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hi All,

I'm trying to write a bit of code that maps each byte in a block of 
Word8's to 3xWord8 using an array; i.e. mapping from 8 bit to 24 bit 
colour (this is an OpenGL application, and I'm using textures).

I should point out that this is experimental code, and I'm still 
learning Haskell (and *loving* it, by the way!), so it probably looks a 
little unpolished.

First, some data:

data Palette = Palette { palRed :: Word8, palGrn :: Word8, palBlu :: Word8 }

palette = listArray (0,49) paletteList
paletteList = [
             Palette 0 0 0,
             Palette 0 0 0,
             Palette 0 0 0,
                .....



Then, my first implementation, which took 57% time under profiling, was:

loadTile :: Int -> Int -> IO (Ptr Word8)
loadTile lat lon = do
     terrainBytes <- readTile lat lon

     -- implementation #1
     mapM_ (paletteMapper terrainBytes rgbBytes) [0..tileSize^2-1]

     free terrainBytes
     return rgbBytes

     where tileSize = 128
           paletteMapper :: Ptr Word8 -> Ptr Word8 -> Int -> IO ()
           paletteMapper tb rgb idx = do
                 v <- peekElemOff tb idx
                 pokeByteOff rgb (idx*3) (palRed (palette!v))
                 pokeByteOff rgb (idx*3+1) (palGrn (palette!v))
                 pokeByteOff rgb (idx*3+2) (palBlu (palette!v))


I tried moving paletterMapper out of the 'where' clause and into the 
top level, which then took only 26% of time - i.e. half the time:


paletteMapper :: Ptr Word8 -> Ptr Word8 -> Int -> IO ()
paletteMapper tb rgb idx = do
    v <- peekElemOff tb idx
    pokeByteOff rgb (idx*3) (palRed (palette!v))
    pokeByteOff rgb (idx*3+1) (palGrn (palette!v))
   pokeByteOff rgb (idx*3+2) (palBlu (palette!v))

loadTile :: Int -> Int -> IO (Ptr Word8)
loadTile lat lon = do
     terrainBytes <- readTile lat lon

     -- implementation #1
     mapM_ (paletteMapper terrainBytes rgbBytes) [0..tileSize^2-1]

     free terrainBytes
     return rgbBytes

     where tileSize = 128


I don't understand why - the functions are the same, except for the 
scope they're in. Can anyone elaborate on what's happening?


Incidentally, I now realise a faster way (14%) is:

loadTile :: Int -> Int -> IO (Ptr Word8)
loadTile lat lon = do

     terrainBytes <- readTile lat lon

     rgbBytes <- mallocBytes (3*(tileSize^2))
     mapM_ (\x -> do
         v <- peekElemOff terrainBytes x
         pokeByteOff rgbBytes (x*3) (palRed (palette!v))
         pokeByteOff rgbBytes (x*3+1) (palGrn (palette!v))
         pokeByteOff rgbBytes (x*3+2) (palBlu (palette!v))
         ) [0..tileSize^2-1]


     free terrainBytes
     return rgbBytes

     where tileSize = 128


(There may be faster/better ways still, I'm all ears :-)

Cheers

Kevin


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

Message: 6
Date: Sat, 9 May 2009 21:11:11 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Performance of function defined in a
        'where' clause
To: beginners@haskell.org
Message-ID: <20090510011111.ga2...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Sat, May 09, 2009 at 05:50:33PM +0100, Kevin Haines wrote:
>
> palette = listArray (0,49) paletteList
> paletteList = [
>             Palette 0 0 0,
>             Palette 0 0 0,
>             Palette 0 0 0,
>               .....

By the way, this should probably be something like

  palette = listArray (0,49) (replicate 50 $ Palette 0 0 0)

Unless, of course, there are things other than Palette 0 0 0 in the
remainder of the list.  If you ever have to copy and paste *anything*
in a Haskell program, warning bells should start going off in your
head. =)

Unfortunately, performance tuning is a black art of which I know
precious little.  Perhaps others will have some good suggestions.

-Brent


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

Message: 7
Date: Sun, 10 May 2009 14:37:07 +1200
From: Andy Elvey <andy.el...@paradise.net.nz>
Subject: Re: [Haskell-beginners] SQL Lexer
To: Patrick LeBoutillier <patrick.leboutill...@gmail.com>
Cc: beginners <beginners@haskell.org>
Message-ID: <4a063dd3.8080...@paradise.net.nz>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Patrick LeBoutillier wrote:
> Hi all,
>
> In the process of writing an SQL parser I started by writing a lexer.
> The code can be found here:
> http://hpaste.org/fastcgi/hpaste.fcgi/view?id=4736#a4736
>
> You can run it like this in ghci:
>
> Prelude SQL.Lexer> runLexer "select * from TABLE order by FIELD"
> [Token Reserved "select",Token Space " ",Token Operator "*",Token
> Space " ",Token Reserved "from",Token Space " ",Token Identifier
> "TABLE",Token Space " ",Token Reserved "order",Token Space " ",Token
> Reserved "by",Token Space " ",Token Identifier "FIELD"]
>
> Since this is pretty much my first Haskell project over 10 lines long,
> I'm looking for some feedback of any kind.
> Ultimately I would like to use this lexer to build a functional SQL
> parser using Parsec.
>
>
> Thanks,
>
> Patrick
>
>   
Hi Patrick - 
I like it!  I'm still a Haskell beginner, but even to me, your code 
seems very clear and easy to understand. 
I've been thinking of doing some simple parsers too, so I was wondering 
- may I use this code of yours as a base for them? 

Well done, and thanks for doing this!
- Andy


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

Message: 8
Date: Sun, 10 May 2009 13:41:14 +0200
From: Peter Verswyvelen <bugf...@gmail.com>
Subject: Re: [Haskell-beginners] Performance of function defined in a
        'where'         clause
To: Kevin Haines <kevin.hai...@ntlworld.com>
Cc: beginners@haskell.org
Message-ID:
        <a88790d10905100441p46706fe2me24190d8ee24c...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Did you compile with -O or -O2?
On Sat, May 9, 2009 at 6:50 PM, Kevin Haines <kevin.hai...@ntlworld.com>wrote:

> Hi All,
>
> I'm trying to write a bit of code that maps each byte in a block of Word8's
> to 3xWord8 using an array; i.e. mapping from 8 bit to 24 bit colour (this is
> an OpenGL application, and I'm using textures).
>
> I should point out that this is experimental code, and I'm still learning
> Haskell (and *loving* it, by the way!), so it probably looks a little
> unpolished.
>
> First, some data:
>
> data Palette = Palette { palRed :: Word8, palGrn :: Word8, palBlu :: Word8
> }
>
> palette = listArray (0,49) paletteList
> paletteList = [
>            Palette 0 0 0,
>            Palette 0 0 0,
>            Palette 0 0 0,
>                .....
>
>
>
> Then, my first implementation, which took 57% time under profiling, was:
>
> loadTile :: Int -> Int -> IO (Ptr Word8)
> loadTile lat lon = do
>    terrainBytes <- readTile lat lon
>
>    -- implementation #1
>    mapM_ (paletteMapper terrainBytes rgbBytes) [0..tileSize^2-1]
>
>    free terrainBytes
>    return rgbBytes
>
>    where tileSize = 128
>          paletteMapper :: Ptr Word8 -> Ptr Word8 -> Int -> IO ()
>          paletteMapper tb rgb idx = do
>                v <- peekElemOff tb idx
>                pokeByteOff rgb (idx*3) (palRed (palette!v))
>                pokeByteOff rgb (idx*3+1) (palGrn (palette!v))
>                pokeByteOff rgb (idx*3+2) (palBlu (palette!v))
>
>
> I tried moving paletterMapper out of the 'where' clause and into the top
> level, which then took only 26% of time - i.e. half the time:
>
>
> paletteMapper :: Ptr Word8 -> Ptr Word8 -> Int -> IO ()
> paletteMapper tb rgb idx = do
>   v <- peekElemOff tb idx
>   pokeByteOff rgb (idx*3) (palRed (palette!v))
>   pokeByteOff rgb (idx*3+1) (palGrn (palette!v))
>  pokeByteOff rgb (idx*3+2) (palBlu (palette!v))
>
> loadTile :: Int -> Int -> IO (Ptr Word8)
> loadTile lat lon = do
>    terrainBytes <- readTile lat lon
>
>    -- implementation #1
>    mapM_ (paletteMapper terrainBytes rgbBytes) [0..tileSize^2-1]
>
>    free terrainBytes
>    return rgbBytes
>
>    where tileSize = 128
>
>
> I don't understand why - the functions are the same, except for the scope
> they're in. Can anyone elaborate on what's happening?
>
>
> Incidentally, I now realise a faster way (14%) is:
>
> loadTile :: Int -> Int -> IO (Ptr Word8)
> loadTile lat lon = do
>
>    terrainBytes <- readTile lat lon
>
>    rgbBytes <- mallocBytes (3*(tileSize^2))
>    mapM_ (\x -> do
>        v <- peekElemOff terrainBytes x
>        pokeByteOff rgbBytes (x*3) (palRed (palette!v))
>        pokeByteOff rgbBytes (x*3+1) (palGrn (palette!v))
>        pokeByteOff rgbBytes (x*3+2) (palBlu (palette!v))
>        ) [0..tileSize^2-1]
>
>
>    free terrainBytes
>    return rgbBytes
>
>    where tileSize = 128
>
>
> (There may be faster/better ways still, I'm all ears :-)
>
> Cheers
>
> Kevin
> _______________________________________________
> 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/20090510/47998c0d/attachment.htm

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

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


End of Beginners Digest, Vol 11, Issue 9
****************************************

Reply via email to