[Haskell-cafe] PNG files

2007-10-29 Thread Tim Newsham
I needed something small for writing out png files and didn't see 
anything, so I wrote my own.  It's not really large or general enough yet 
to warrant a full package.  It wouldn't require much work to support other 
variant formats, such as color.


 Png.hs 
{-
A small library for creating monochrome PNG files.
This file is placed into the public domain.
Dependencies: Zlib.
-}
module Png (png) where
import Data.Array
import Data.Bits
import Data.List
import Data.Word
import qualified Codec.Compression.Zlib as Z
import qualified Data.ByteString.Lazy as B

be8 :: Word8 -> B.ByteString
be8 x = B.singleton x

be32 :: Word32 -> B.ByteString
be32 x = B.pack [fromIntegral (x `shiftR` sh) | sh <- [24,16,8,0]]

pack :: String -> B.ByteString
pack xs = B.pack $ map (fromIntegral.fromEnum) xs

unpack :: B.ByteString -> String
unpack xs = map (toEnum.fromIntegral) (B.unpack xs)

hdr, iHDR, iDAT, iEND :: B.ByteString
hdr = pack "\137\80\78\71\13\10\26\10"
iHDR = pack "IHDR"
iDAT = pack "IDAT"
iEND = pack "IEND"

chunk :: B.ByteString -> B.ByteString -> [B.ByteString]
chunk tag xs = [be32 (fromIntegral $ B.length xs), dat, be32 (crc dat)]
where dat = B.append tag xs

-- | Return a monochrome PNG file from a two dimensional bitmap
-- stored in a list of lines represented as a list of booleans.
png :: [[Bool]] -> String
png dat = unpack $ B.concat $ hdr : concat [ihdr, imgdat, iend]
where height = fromIntegral $ length dat
  width = fromIntegral $ length (head dat)
  ihdr = chunk iHDR (B.concat [
be32 width, be32 height, be8 1, be8 0, be8 0, be8 0, be8 
0])

  imgdat = chunk iDAT (Z.compress imgbits)
  imgbits = B.concat $ map scanline dat
  iend = chunk iEND B.empty

scanline :: [Bool] -> B.ByteString
scanline dat = 0 `B.cons` bitpack dat

bitpack' :: [Bool] -> Word8 -> Word8 -> B.ByteString
bitpack' [] n b = if b /= 0x80 then B.singleton n else B.empty
bitpack' (x:xs) n b =
if b == 1
then v `B.cons` bitpack' xs 0 0x80
else bitpack' xs v (b `shiftR` 1)
where v = if x then n else n .|. b

bitpack :: [Bool] -> B.ByteString
bitpack xs = bitpack' xs 0 0x80

crc :: B.ByteString -> Word32
crc xs = updateCrc 0x xs `xor` 0x

updateCrc :: Word32 -> B.ByteString -> Word32
updateCrc = B.foldl' crcStep

crcStep :: Word32 -> Word8 -> Word32
crcStep crc ch = (crcTab ! n) `xor` (crc `shiftR` 8)
where n = fromIntegral (crc `xor` fromIntegral ch)

crcTab :: Array Word8 Word32
crcTab = array (0,255) $ zip [0..255] $ flip map [0..255] (\n ->
foldl' (\c k -> if c .&. 1 == 1
  then 0xedb88320 `xor` (c `shiftR` 1)
  else c `shiftR` 1) n [0..7])

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie Question on Setting the GHC Search Path

2007-10-29 Thread Benjamin L. Russell
You're right; it works without the double-quotes.

Problem solved.  Thanks!

Benjamin L. Russell

--- Olivier Boudry <[EMAIL PROTECTED]> wrote:

> In GHC it works without the " and don't work with
> them:
> 
> Prelude> :cd C:\Documents and Settings
> Prelude> :! pwd
> C:\Documents and Settings
> 
> Olivier.
> 
> On 10/29/07, Benjamin L. Russell
> <[EMAIL PROTECTED]> wrote:
> >
> > Please pardon this intrusion for an elementary
> > question on setting the GHC search path.
> >
> > I have installed GHC on my work Windows XP
> machine,
> > and would like to be able to search for files in
> the
> > following directory:
> >
> > D:\From C Drive\Documents and
> > Settings\DekuDekuplex\Programming
> Practice\Haskell\GHC
> >
> > However, when I type the following command into
> the
> > GHC interpreter:
> >
> > :cd "D:\From C Drive\Documents and
> > Settings\DekuDekuplex\Programming
> > Practice\Haskell\GHC"
> >
> > I get the following error message:
> >
> > *** Exception: "D:\From C Drive\Documents and
> > Settings\DekuDekuplex\Programming
> > Practice\Haskell\GHC": setCurrentDirectory:
> invalid
> > argument (Invalid argument)
> >
> > Yet, for testing purposes, when I type the
> following
> > command:
> >
> > :cd cygwin
> >
> > I do not get any error message.
> >
> > There seems to be a problem with the spaces in the
> > filename.  However, I would like to be able to use
> the
> > "D:\From C Drive\Documents and
> > Settings\DekuDekuplex\Programming
> > Practice\Haskell\GHC" directory for GHC
> programming
> > practice, because I keep my practice work for my
> other
> > programming languages in the same
> > super-super-directory.
> >
> > Does anybody know a way to specify "D:\From C
> > Drive\Documents and
> Settings\DekuDekuplex\Programming
> > Practice\Haskell\GHC" as a directory in the search
> > path for GHC?
> >
> > Benjamin L. Russell
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> >
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> > ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Image manipulation

2007-10-29 Thread Tim Chevalier
On 10/29/07, Stefan O'Rear <[EMAIL PROTECTED]> wrote:
> The OP specified that the images are around 5M in size, and need to be
> rescaled, so we're talking about quite a bit of computation per shellout
> (tens to hundreds of megacycles).  Are context switches that slow?
>

I don't know. I'd have to do the experiment before I could give an
answer to that. But yeah, if I were the OP, I would probably start by
trying to write a shell script (or a simple Haskell program with calls
to "system") to do what I wanted, and see if that was adequate.

Cheers,
Tim


-- 
Tim Chevalier * catamorphism.org * Often in error, never in doubt
"Work a little bit harder on improving your low self-esteem, you
stupid freak" -- "Weird Al" Yankovic
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Image manipulation

2007-10-29 Thread Stefan O'Rear
On Mon, Oct 29, 2007 at 02:39:58PM -0700, Tim Chevalier wrote:
> [redirecting to haskell-cafe]
> On 10/29/07, Brent Yorgey <[EMAIL PROTECTED]> wrote:
> > Haskell is a wonderful language, so I hate to say this...but personally I
> > don't see the benefit of using Haskell here, unless the manipulations you
> > want to do are very complex.  Some simple shell (or
> > perl/python/ruby/whatever) scripts to glue together some calls to convert
> > (or possibly other ImageMagick utilities) ought to do the job just fine.
> >
> 
> If you're doing many image transformations, invoking an external
> program like convert will get expensive due to context-switching. So
> that's why something like the (not-yet-existent) bindings for
> ImageMagick-as-a-library might be useful.
> 
> I agree that laziness probably isn't going to be helpful, but there
> may be interesting things to be done that are enabled by purity and
> higher-order-functions. I'm working on the ImageMagick bindings
> because I'm curious to find out. There are obvious things like being
> able to define compositions of transformations -- which is easy to do
> when you're calling library functions in-memory, and less so if you're
> using a separate executable -- but maybe there are more interesting
> applications too.

The OP specified that the images are around 5M in size, and need to be
rescaled, so we're talking about quite a bit of computation per shellout
(tens to hundreds of megacycles).  Are context switches that slow?

Stefan


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Image manipulation

2007-10-29 Thread Tim Chevalier
[redirecting to haskell-cafe]
On 10/29/07, Brent Yorgey <[EMAIL PROTECTED]> wrote:
> Haskell is a wonderful language, so I hate to say this...but personally I
> don't see the benefit of using Haskell here, unless the manipulations you
> want to do are very complex.  Some simple shell (or
> perl/python/ruby/whatever) scripts to glue together some calls to convert
> (or possibly other ImageMagick utilities) ought to do the job just fine.
>

If you're doing many image transformations, invoking an external
program like convert will get expensive due to context-switching. So
that's why something like the (not-yet-existent) bindings for
ImageMagick-as-a-library might be useful.

I agree that laziness probably isn't going to be helpful, but there
may be interesting things to be done that are enabled by purity and
higher-order-functions. I'm working on the ImageMagick bindings
because I'm curious to find out. There are obvious things like being
able to define compositions of transformations -- which is easy to do
when you're calling library functions in-memory, and less so if you're
using a separate executable -- but maybe there are more interesting
applications too.

Cheers,
Tim

-- 
Tim Chevalier * catamorphism.org * Often in error, never in doubt
"Thus spake the Master Programmer: When you have learned to snatch the
error code from the trap frame, it will be time for you to leave."--J.
Geoffrey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Tim Sweeney and multi-cores .... and Haskell

2007-10-29 Thread Dan Weston
I didn't see anything either. But a search of the site finds one article 
that mentions Haskell exactly twice (no Tom Sweeney though). An 
interesting overview of the Language Wars (French translation available 
as well):


The Semicolon Wars:
  Every programmer knows there is one true programming language. A new 
one every week

by Brian Hayes

http://www.americanscientist.org/template/AssetDetail/assetid/51982

Sebastian Sylvan wrote:

On 28/10/2007, Galchin Vasili <[EMAIL PROTECTED]> wrote:

http://www.americanscientist.org/content/AMSCI/AMSCI/ArticleAltFormat/2007102151724_866.pdf



Am I missing something? I didn't see anything about Haskell, nor Tim
Sweeney for that matter, in that article.




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Tim Sweeney and multi-cores .... and Haskell

2007-10-29 Thread Galchin Vasili
oops .. here is the Tim Sweeney talk
http://lambda-the-ultimate.org/node/1277 << The Next Mainstream Programming
Languages  If I remember correctly argues that with multicores coming that
current programming language paradigmns will not "cut the mustard" due to
current bad parallelism models. I guess this would bring into mind Simon
Peyton Jone's and Simon Marlow's STM research .

Regards, Bill


On 10/28/07, Sebastian Sylvan <[EMAIL PROTECTED]> wrote:
>
> On 28/10/2007, Galchin Vasili <[EMAIL PROTECTED]> wrote:
> >
> http://www.americanscientist.org/content/AMSCI/AMSCI/ArticleAltFormat/2007102151724_866.pdf
>
>
> Am I missing something? I didn't see anything about Haskell, nor Tim
> Sweeney for that matter, in that article.
>
> --
> Sebastian Sylvan
> +44(0)7857-300802
> UIN: 44640862
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie Question on Setting the GHC Search Path

2007-10-29 Thread Olivier Boudry
In GHC it works without the " and don't work with them:

Prelude> :cd C:\Documents and Settings
Prelude> :! pwd
C:\Documents and Settings

Olivier.

On 10/29/07, Benjamin L. Russell <[EMAIL PROTECTED]> wrote:
>
> Please pardon this intrusion for an elementary
> question on setting the GHC search path.
>
> I have installed GHC on my work Windows XP machine,
> and would like to be able to search for files in the
> following directory:
>
> D:\From C Drive\Documents and
> Settings\DekuDekuplex\Programming Practice\Haskell\GHC
>
> However, when I type the following command into the
> GHC interpreter:
>
> :cd "D:\From C Drive\Documents and
> Settings\DekuDekuplex\Programming
> Practice\Haskell\GHC"
>
> I get the following error message:
>
> *** Exception: "D:\From C Drive\Documents and
> Settings\DekuDekuplex\Programming
> Practice\Haskell\GHC": setCurrentDirectory: invalid
> argument (Invalid argument)
>
> Yet, for testing purposes, when I type the following
> command:
>
> :cd cygwin
>
> I do not get any error message.
>
> There seems to be a problem with the spaces in the
> filename.  However, I would like to be able to use the
> "D:\From C Drive\Documents and
> Settings\DekuDekuplex\Programming
> Practice\Haskell\GHC" directory for GHC programming
> practice, because I keep my practice work for my other
> programming languages in the same
> super-super-directory.
>
> Does anybody know a way to specify "D:\From C
> Drive\Documents and Settings\DekuDekuplex\Programming
> Practice\Haskell\GHC" as a directory in the search
> path for GHC?
>
> Benjamin L. Russell
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] placing modules in the module hierarchy

2007-10-29 Thread Henning Thielemann

On Mon, 29 Oct 2007, Dimitry Golubovsky wrote:

> So, I'd suggest for the Grapefruit library: whatever is specific to
> this library, goes under Graphics.UI.Grapefruit. Whatever may be
> commonly used elsewhere (say some useful data structures) might go
> under "Data". So, if FRP signals are usable outside the Grapefruit,
> they might go to Control.

... and they should reside in a separate package.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] placing modules in the module hierarchy

2007-10-29 Thread Dimitry Golubovsky
Hi,

Long ago (back in 2001), there was a message in the Haskell mailing
list, archived e. g. here:

http://www.mail-archive.com/[EMAIL PROTECTED]/msg08187.html

and what it refers to is here:

http://www.cs.york.ac.uk/fp/libraries/layout.html

which goes for "Graphics.UI.  etc"

I used this approach in my script to cabalize Fudgets: everything was
placed below "Graphics.UI.Fudgets" (original Fudgets library used
plain module space).

I am currently working on another stuff related to Haskell GUI for web
browser, and us the same approach: everything goes under
Graphics.UI.

So, I think, despite this creates longer paths in the hierarchy, the
more specialized the stuff is, the deeper in the hierarchy it should
be pushed.

Slightly off topic, this is IMHO the same problem that we have in
Linux packages/filesystem layout: every package containing binaries,
places them into say /usr/bin. Then, if the two packages have a binary
with the same name, this leads to conflict (HSSFFIG has a program
named "splitter". Another package in Debian also had a binary with the
same name. they conflicted. To resolve it' I'd have to rename my
binary to say hsffig-splitter. Should every package be installed into
its own subtree, such conflicts wouldn't arise). So, to my personal
opinion (which is in agreement with the proposal mentioned) each
package has to have its own tree not crossing with other packages'
tree.

So, I'd suggest for the Grapefruit library: whatever is specific to
this library, goes under Graphics.UI.Grapefruit. Whatever may be
commonly used elsewhere (say some useful data structures) might go
under "Data". So, if FRP signals are usable outside the Grapefruit,
they might go to Control.

Thanks.

-- 
Dimitry Golubovsky

Anywhere on the Web
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie Question on Setting the GHC Search Path

2007-10-29 Thread Stefan O'Rear
On Mon, Oct 29, 2007 at 04:25:45AM -0700, Benjamin L. Russell wrote:
> One factor that is slightly unusual about this
> phenomenon is that it only occurs with GHC, but not
> with Hugs 98.  Typing 
> 
> :cd "D:\From C Drive\Documents and
> Settings\DekuDekuplex\Programming
> Practice\Haskell\GHC"

Are you sure it has anything to do with spaces?  Exactly one of your
test paths has backslashes, and it's not the working one.

Stefan


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] placing modules in the module hierarchy

2007-10-29 Thread Isaac Dupree

Wolfgang Jeltsch wrote:
Since the Control.Grapefruit subtree would probably only consist of 
Control.Grapefruit.Signal and submodules, I’d prefer to just use 
Control.Signal and Control.Signal.*.  But this would pose the problem that no 
other FRP library could use Control.Signal without conflicting with 
Grapefruit.


One _ideal_ is to develop a consensus in the community for a FRP Signal 
library, one that is good enough that Grapefruit could use it.  (If the 
library is inherently Grapefruit-specific, do use 
Control.Signal.Grapefruit or Control.Grapefruit.Signal.)  Of course that 
ideal is not always possible, and best-library consensuses do change 
over the years -- but we've been doing it a lot anyway.


Isaac
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fusion for fun and profi (Was: newbie optimization question)

2007-10-29 Thread Isaac Dupree

Don Stewart wrote:

default(Int)

divisors i   = filter (\j -> i `rem`j == 0) (enumFromTo 1 (i-1))
main = print $ filter (\i -> i == sum (divisors i)) (enumFromTo 1 1)


...

So almost identical types to the C program (bar for the return [Int]). 


Finally, we can manually translate the C code into a confusing set of nested
loops with interleaved IO,


how lazy is `print` supposed to be?  If it's strict, we need to return / 
accumulate a list (and in this case, that is not very time-consuming 
because there are only four numbers in the list)


from http://haskell.org/onlinereport/standard-prelude.html

print x=  putStrLn (show x)

show on lists is lazy and doesn't matter that it's not for Ints

putStrLn   :: String -> IO ()
putStrLn s =  do putStr s
 putStr "\n"

putStr :: String -> IO ()
putStr s   =  mapM_ putChar s

okay, mapM_ makes it lazy.

putChar:: Char -> IO ()
putChar=  primPutChar

(It's easy to get confused with OS buffering effects too...)

so it should ALL be able to fuse, with no intermediate lists, I think 
(not sure about [Char] from show... or whether fusion works with IO 
sequencing...)



Isaac
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Quasiquotations part of GHC?

2007-10-29 Thread Joel Reymont

Folks,

Did quasiquotations ever make it into the GHC tree?

They were implemented as a patch to 6.7.

Thanks, Joel

--
http://wagerlabs.com





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: newbie optimization question

2007-10-29 Thread Peter Hercek

OK, if somebody wants to speculate (and if it even makes sense for
such a microbenchmark) here are some more data.
Except different OS and C++ compiler also processor is different.
On my side it was AMD Athlon 64 X2 4800+ (2.4GHz, 2x1MiB L2 cache
non-shared; C&Q was not switched off during the test). The system has
2GiB RAM. The C++ version had working set about 1.7 MiB, ghc version
had it about 2 times bigger.

Peter.

Dusan Kolar wrote:

Hello all,

 just to compare the stuff, I get quite other results being on other OS. 
Thus, the result of C++ compiler may not be that interesting as I do not 
have the one presented below.


My machine:
Linux 2.6.23-ARCH #1 SMP PREEMPT Mon Oct 22 12:50:26 CEST 2007 x86_64 
Intel(R) Core(TM)2 CPU  6600 @ 2.40GHz GenuineIntel GNU/Linux


Compilers:
g++ --version
g++ (GCC) 4.2.2
Copyright (C) 2007 Free Software Foundation, Inc.
This is free software; see the source for copying conditions.  There is NO
warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.

ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.6.1

Measurement:
compiled with ghc -O2
time ./mainInteger
real0m4.866s
user0m4.843s
sys 0m0.020s

compiled with ghc -O2
time ./mainInt64
real0m2.213s
user0m2.210s
sys 0m0.003s

compiled with ghc -O2
time ./mainInt
real0m1.149s
user0m1.143s
sys 0m0.003s

compiled with g++ -O3
time ./mainC
real0m0.271s
user0m0.270s
sys 0m0.000s

I don't know what is the reason, but the difference between Int, Int64 
and Integer is not that dramatic as in example below, nevertheless, the 
difference between GHC and GNU C++ is very bad :-\


Dusan


Peter Hercek wrote:

Derek Elkins wrote:


Try with rem instead of mod.

(What the heck is with bottom?)


The bottom was there by error and I was lazy to redo
 the tests so I rather posted exactly what I was
 doing. I do not know the compiler that good to be
 absolutely sure it cannot have impact on result
 ... so I rather did not doctor what I did :-)

Ok, rem did help quite a bit. Any comments why it is so?

Here are summary of results for those interested. I run
 all the tests once again. Haskell was about 13% slower
 than C++.

MS cl.exe options: /Ox /G7 /MD
ghc options: -O2

C++ version:  1.000; 0.984; 0.984
Haskell version specialized to Int: 1.125; 1.125; 1.109
Haskell version specialized to Integer: 8.781; 8.813; 8.813
Haskell version specialized to Int64: 9.781; 9.766; 9.831

The code:

% cat b.hs
module Main (divisors, perfect, main) where
import Data.Int

divisors :: Int -> [Int]
divisors i = [j | j<-[1..i-1], i `rem` j == 0]

perfect :: [Int]
perfect = [i | i<-[1..1], i == sum (divisors i)]

main = print perfect

% cat b.cpp
#include 
using namespace std;

int main() {
  for (int i = 1; i <= 1; i++) {
int sum = 0;
for (int j = 1; j < i; j++)
  if (i % j == 0)
sum += j;
if (sum == i)
  cout << i << " ";
  }
  return 0;
}

%

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] viewing HS files in Firefox

2007-10-29 Thread Thomas Hartman
I would love an answer to this as well.



Isaac Dupree <[EMAIL PROTECTED]> 
Sent by: [EMAIL PROTECTED]
10/27/2007 06:48 PM

To
Haskell-cafe 
cc

Subject
[Haskell-cafe] viewing HS files in Firefox






When I try to go to one of the Module.hs files, e.g. on 
darcs.haskell.org, it now has type HS and Firefox refuses to display it 
(and only lets me download it).  Does anyone know how to make Firefox 
treat certain file types as others (HS as plain text, in particular)? 
so that I can browse them with any convenience

Thanks,
Isaac
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: newbie optimization question

2007-10-29 Thread Daniel Fischer
Am Montag, 29. Oktober 2007 13:49 schrieb Dusan Kolar:
> Hello all,
>
>   just to compare the stuff, I get quite other results being on other
> OS. Thus, the result of C++ compiler may not be that interesting as I do
> not have the one presented below.

Just to chime in, my results with the code below:
[EMAIL PROTECTED]:~> uname -a
Linux linux 2.4.20-4GB-athlon #1 Mon Mar 17 17:56:47 UTC 2003 i686 unknown 
unknown GNU/Linux

on a 1200 MHz Duron

g++ is version 3.3, C++ code compiled with -O3, Haskell with -O2 (GHC 6.6.1)
[EMAIL PROTECTED]:~> time ./mainC
6 28 496 8128
real0m1.945s
user0m1.910s
sys 0m0.010s
[EMAIL PROTECTED]:~> time ./mainInt
[6,28,496,8128]

real0m2.407s
user0m2.300s
sys 0m0.010s
[EMAIL PROTECTED]:~> time ./mainInt64
[6,28,496,8128]

real0m24.009s
user0m23.900s
sys 0m0.050s
[EMAIL PROTECTED]:~> time ./mainInteger
[6,28,496,8128]

real0m21.555s
user0m20.870s
sys 0m0.010s

So Int is not so much slower than C, Int64 and Integer dramatically slower 
with Integer beating Int64 here, too.

Cheers,
Daniel

>
> My machine:
> Linux 2.6.23-ARCH #1 SMP PREEMPT Mon Oct 22 12:50:26 CEST 2007 x86_64
> Intel(R) Core(TM)2 CPU  6600 @ 2.40GHz GenuineIntel GNU/Linux
>
> Compilers:
> g++ --version
> g++ (GCC) 4.2.2
> Copyright (C) 2007 Free Software Foundation, Inc.
> This is free software; see the source for copying conditions.  There is NO
> warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
>
> ghc --version
> The Glorious Glasgow Haskell Compilation System, version 6.6.1
>
> Measurement:
> compiled with ghc -O2
> time ./mainInteger
> real0m4.866s
> user0m4.843s
> sys 0m0.020s
>
> compiled with ghc -O2
> time ./mainInt64
> real0m2.213s
> user0m2.210s
> sys 0m0.003s
>
> compiled with ghc -O2
> time ./mainInt
> real0m1.149s
> user0m1.143s
> sys 0m0.003s
>
> compiled with g++ -O3
> time ./mainC
> real0m0.271s
> user0m0.270s
> sys 0m0.000s
>
> I don't know what is the reason, but the difference between Int, Int64
> and Integer is not that dramatic as in example below, nevertheless, the
> difference between GHC and GNU C++ is very bad :-\
>
> Dusan

> > The code:
> >
> > % cat b.hs
> > module Main (divisors, perfect, main) where
> > import Data.Int
> >
> > divisors :: Int -> [Int]
> > divisors i = [j | j<-[1..i-1], i `rem` j == 0]
> >
> > perfect :: [Int]
> > perfect = [i | i<-[1..1], i == sum (divisors i)]
> >
> > main = print perfect
> >
> > % cat b.cpp
> > #include 
> > using namespace std;
> >
> > int main() {
> >   for (int i = 1; i <= 1; i++) {
> > int sum = 0;
> > for (int j = 1; j < i; j++)
> >   if (i % j == 0)
> > sum += j;
> > if (sum == i)
> >   cout << i << " ";
> >   }
> >   return 0;
> > }
> >
> > %

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: newbie optimization question

2007-10-29 Thread Simon Marlow

Peter Hercek wrote:

Daniel Fischer wrote:
What perpetually puzzles me is that in C long long int has very good 
performance, *much* faster than gmp, in Haskell, on my computer, Int64 
is hardly faster than Integer. 


I tried the example with Int64 and Integer. The integer version
 was actually quicker ... which is the reason I decided to post
 the results.

C++ version times: 1.125; 1.109; 1.125
Int32 cpu times: 3.203; 3.172; 3.172
Int64 cpu times: 11.734; 11.797; 11.844
Integer cpu times: 9.609; 9.609; 9.500

Interesting that Int64 is *slower* than Integer.


I can believe that.  Integer is actually optimised for small values: 
there's a specialised representation for values that fit in a single word 
that avoids calling out to the GMP library.


As Stefan pointed out, there's a lot of room to improve the performance of 
Int64, it's just never been a high priority.


Cheers,
Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: newbie optimization question

2007-10-29 Thread Dusan Kolar

Hello all,

 just to compare the stuff, I get quite other results being on other 
OS. Thus, the result of C++ compiler may not be that interesting as I do 
not have the one presented below.


My machine:
Linux 2.6.23-ARCH #1 SMP PREEMPT Mon Oct 22 12:50:26 CEST 2007 x86_64 
Intel(R) Core(TM)2 CPU  6600 @ 2.40GHz GenuineIntel GNU/Linux


Compilers:
g++ --version
g++ (GCC) 4.2.2
Copyright (C) 2007 Free Software Foundation, Inc.
This is free software; see the source for copying conditions.  There is NO
warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.

ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.6.1

Measurement:
compiled with ghc -O2
time ./mainInteger
real0m4.866s
user0m4.843s
sys 0m0.020s

compiled with ghc -O2
time ./mainInt64
real0m2.213s
user0m2.210s
sys 0m0.003s

compiled with ghc -O2
time ./mainInt
real0m1.149s
user0m1.143s
sys 0m0.003s

compiled with g++ -O3
time ./mainC
real0m0.271s
user0m0.270s
sys 0m0.000s

I don't know what is the reason, but the difference between Int, Int64 
and Integer is not that dramatic as in example below, nevertheless, the 
difference between GHC and GNU C++ is very bad :-\


Dusan


Peter Hercek wrote:

Derek Elkins wrote:


Try with rem instead of mod.

(What the heck is with bottom?)


The bottom was there by error and I was lazy to redo
 the tests so I rather posted exactly what I was
 doing. I do not know the compiler that good to be
 absolutely sure it cannot have impact on result
 ... so I rather did not doctor what I did :-)

Ok, rem did help quite a bit. Any comments why it is so?

Here are summary of results for those interested. I run
 all the tests once again. Haskell was about 13% slower
 than C++.

MS cl.exe options: /Ox /G7 /MD
ghc options: -O2

C++ version:  1.000; 0.984; 0.984
Haskell version specialized to Int: 1.125; 1.125; 1.109
Haskell version specialized to Integer: 8.781; 8.813; 8.813
Haskell version specialized to Int64: 9.781; 9.766; 9.831

The code:

% cat b.hs
module Main (divisors, perfect, main) where
import Data.Int

divisors :: Int -> [Int]
divisors i = [j | j<-[1..i-1], i `rem` j == 0]

perfect :: [Int]
perfect = [i | i<-[1..1], i == sum (divisors i)]

main = print perfect

% cat b.cpp
#include 
using namespace std;

int main() {
  for (int i = 1; i <= 1; i++) {
int sum = 0;
for (int j = 1; j < i; j++)
  if (i % j == 0)
sum += j;
if (sum == i)
  cout << i << " ";
  }
  return 0;
}

%

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


--

Dusan Kolartel: +420 54 114 1238
UIFS FIT VUT Brno  fax: +420 54 114 1270
Bozetechova 2   e-mail: [EMAIL PROTECTED]
Brno 612 66
Czech Republic

--

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] newbie optimization question

2007-10-29 Thread Prabhakar Ragde

Ryan Dickie wrote:
One thing I've noticed is that turning on optimizations significantly 
increases the speed of haskell code. Are you comparing code between 
languages with -O2 or without opts?


I had done no optimization, but neither -O nor -O2 make a significant 
difference in either the C or Haskell programs. But using `rem` instead 
of `mod`, together with the type annotation, makes the two programs take 
pretty much the same amount of time. --PR

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Fusing foldr's

2007-10-29 Thread Bulat Ziganshin
Hello Josef,

Monday, October 29, 2007, 2:08:54 PM, you wrote:

>> that can maybe account for the additional time savings. I'm not sure
>> how to verify that this is the case though.
>>
> Bulat kindly suggested I use +RTS -s to monitor the garbage collectors
> behavior. It seems my hypothesis was right.

you may also look at these data:

  1,225,416 bytes allocated in the heap
152,984 bytes copied during GC (scavenged)
  8,448 bytes copied during GC (not scavenged)
 86,808 bytes maximum residency (1 sample(s))

  3 collections in generation 0 (  0.00s)
  1 collections in generation 1 (  0.00s)

if your hypothesis is true, amount of data copied and number of
generation-1 collection should be much less in the second case


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie Question on Setting the GHC Search Path

2007-10-29 Thread Benjamin L. Russell
One factor that is slightly unusual about this
phenomenon is that it only occurs with GHC, but not
with Hugs 98.  Typing 

:cd "D:\From C Drive\Documents and
Settings\DekuDekuplex\Programming
Practice\Haskell\GHC"

in Hugs 98 does not cause an error, but typing the
same command in GHC does.  It seems that Hugs 98
allows spaces in filenames/paths, but GHC doesn't.

Is there any way to configure GHC so that it accepts
the same type of filenames/paths as Hugs 98?

Benjamin L. Russell

--- "Benjamin L. Russell" <[EMAIL PROTECTED]>
wrote:

> Please pardon this intrusion for an elementary
> question on setting the GHC search path.
> 
> I have installed GHC on my work Windows XP machine,
> and would like to be able to search for files in the
> following directory:
> 
> D:\From C Drive\Documents and
> Settings\DekuDekuplex\Programming
> Practice\Haskell\GHC
> 
> However, when I type the following command into the
> GHC interpreter:
> 
> :cd "D:\From C Drive\Documents and
> Settings\DekuDekuplex\Programming
> Practice\Haskell\GHC"
> 
> I get the following error message:
> 
> *** Exception: "D:\From C Drive\Documents and
> Settings\DekuDekuplex\Programming
> Practice\Haskell\GHC": setCurrentDirectory: invalid
> argument (Invalid argument)
> 
> Yet, for testing purposes, when I type the following
> command:
> 
> :cd cygwin
> 
> I do not get any error message.
> 
> There seems to be a problem with the spaces in the
> filename.  However, I would like to be able to use
> the
> "D:\From C Drive\Documents and
> Settings\DekuDekuplex\Programming
> Practice\Haskell\GHC" directory for GHC programming
> practice, because I keep my practice work for my
> other
> programming languages in the same
> super-super-directory.
> 
> Does anybody know a way to specify "D:\From C
> Drive\Documents and
> Settings\DekuDekuplex\Programming
> Practice\Haskell\GHC" as a directory in the search
> path for GHC?
> 
> Benjamin L. Russell
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fusing foldr's

2007-10-29 Thread Josef Svenningsson
On 10/29/07, Josef Svenningsson <[EMAIL PROTECTED]> wrote:
> But using those flags yielded a very interesting result:
>
> avgP: 4.3s
>
> Superlinear speedup!? As you say, I would have expected something
> slightly larger than 9s. I think what happens here is that for avg4
> the entire list has to be kept in memory between the two traversals
> whereas for avgP the beginning of the list can be garbage collected
> incrementally as the two threads traverse it. This could mean that the
> list never moves to the second generation in the memory manager and
> that can maybe account for the additional time savings. I'm not sure
> how to verify that this is the case though.
>
Bulat kindly suggested I use +RTS -s to monitor the garbage collectors
behavior. It seems my hypothesis was right.

avg4:
387 Mb total memory in use
MUT   time2.43s  (  2.47s elapsed)
GCtime   15.32s  ( 16.05s elapsed)

avgP (+RTS -N2):
3 Mb total memory in use
MUT   time4.61s  (  2.51s elapsed)
GCtime0.04s  (  0.06s elapsed)

So it seems that the garbage collector takes an awful lot of time when
we allocate a big list like this. Hmmm. Strikes me as somewhat
suboptimal.

Cheers,

/Josef
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: newbie optimization question

2007-10-29 Thread Peter Hercek

Rodrigo Queiro wrote:

Why do you expose perfect and divisors? Maybe if you just expose main,
perfect and divisors will be inlined (although this will only save
10,000 function entries, so will probably have negligible effect).


I exposed them so that I can check types in ghci.
Hiding them does not seem to have noticeable effect.

Thanks,
Peter.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fusing foldr's

2007-10-29 Thread Josef Svenningsson
On 10/28/07, Isaac Dupree <[EMAIL PROTECTED]> wrote:
> Josef Svenningsson wrote:
> > Less bogus timing:
> > avg4: 18.0s
> > avgS: 2.2s
> > avgP: 17.4s
> >
> > OK, so these figures make an even stronger case for my conclusion :-)
> > Single traversal can be much faster than multiple traversals *when
> > done right*.
>
> Did you use +RTS -N2 on your program (or whatever it is that makes GHC
> actually use multiple threads? or is that not necessary?)  Anyway I
> assume you wouldn't get better than 9.0s, which is still much worse than
> 2.2s.
>
Oh, this is getting embarrassing.. Indeed, I forgot to use +RTS -N2.
But using those flags yielded a very interesting result:

avgP: 4.3s

Superlinear speedup!? As you say, I would have expected something
slightly larger than 9s. I think what happens here is that for avg4
the entire list has to be kept in memory between the two traversals
whereas for avgP the beginning of the list can be garbage collected
incrementally as the two threads traverse it. This could mean that the
list never moves to the second generation in the memory manager and
that can maybe account for the additional time savings. I'm not sure
how to verify that this is the case though.

Cheers,

/Josef
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: newbie optimization question

2007-10-29 Thread Rodrigo Queiro
rem is faster because it has slightly different behaviour to mod, and
there happens to be an intel instruction that maps more directly to
rem than to mod, thus making it much faster on intel processors.

Why do you expose perfect and divisors? Maybe if you just expose main,
perfect and divisors will be inlined (although this will only save
10,000 function entries, so will probably have negligible effect).

Rodrigo

On 29/10/2007, Peter Hercek <[EMAIL PROTECTED]> wrote:
> Derek Elkins wrote:
> >
> > Try with rem instead of mod.
> >
> > (What the heck is with bottom?)
>
> The bottom was there by error and I was lazy to redo
>   the tests so I rather posted exactly what I was
>   doing. I do not know the compiler that good to be
>   absolutely sure it cannot have impact on result
>   ... so I rather did not doctor what I did :-)
>
> Ok, rem did help quite a bit. Any comments why it is so?
>
> Here are summary of results for those interested. I run
>   all the tests once again. Haskell was about 13% slower
>   than C++.
>
> MS cl.exe options: /Ox /G7 /MD
> ghc options: -O2
>
> C++ version:  1.000; 0.984; 0.984
> Haskell version specialized to Int: 1.125; 1.125; 1.109
> Haskell version specialized to Integer: 8.781; 8.813; 8.813
> Haskell version specialized to Int64: 9.781; 9.766; 9.831
>
> The code:
>
> % cat b.hs
> module Main (divisors, perfect, main) where
> import Data.Int
>
> divisors :: Int -> [Int]
> divisors i = [j | j<-[1..i-1], i `rem` j == 0]
>
> perfect :: [Int]
> perfect = [i | i<-[1..1], i == sum (divisors i)]
>
> main = print perfect
>
> % cat b.cpp
> #include 
> using namespace std;
>
> int main() {
>for (int i = 1; i <= 1; i++) {
>  int sum = 0;
>  for (int j = 1; j < i; j++)
>if (i % j == 0)
>  sum += j;
>  if (sum == i)
>cout << i << " ";
>}
>return 0;
> }
>
> %
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] binary operator modifiers

2007-10-29 Thread Bulat Ziganshin
Hello Tim,

Monday, October 29, 2007, 10:36:18 AM, you wrote:

> or go through the trouble of defining a bunch of binops

> Is there any way in Haskell to modify binops in this way and still
> be able to use them infix?

Template Haskell looks like an perfect tool for implementing this

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: newbie optimization question

2007-10-29 Thread Peter Hercek

Derek Elkins wrote:


Try with rem instead of mod.

(What the heck is with bottom?)


The bottom was there by error and I was lazy to redo
 the tests so I rather posted exactly what I was
 doing. I do not know the compiler that good to be
 absolutely sure it cannot have impact on result
 ... so I rather did not doctor what I did :-)

Ok, rem did help quite a bit. Any comments why it is so?

Here are summary of results for those interested. I run
 all the tests once again. Haskell was about 13% slower
 than C++.

MS cl.exe options: /Ox /G7 /MD
ghc options: -O2

C++ version:  1.000; 0.984; 0.984
Haskell version specialized to Int: 1.125; 1.125; 1.109
Haskell version specialized to Integer: 8.781; 8.813; 8.813
Haskell version specialized to Int64: 9.781; 9.766; 9.831

The code:

% cat b.hs
module Main (divisors, perfect, main) where
import Data.Int

divisors :: Int -> [Int]
divisors i = [j | j<-[1..i-1], i `rem` j == 0]

perfect :: [Int]
perfect = [i | i<-[1..1], i == sum (divisors i)]

main = print perfect

% cat b.cpp
#include 
using namespace std;

int main() {
  for (int i = 1; i <= 1; i++) {
int sum = 0;
for (int j = 1; j < i; j++)
  if (i % j == 0)
sum += j;
if (sum == i)
  cout << i << " ";
  }
  return 0;
}

%

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: newbie optimization question

2007-10-29 Thread Peter Hercek

Don Stewart wrote:

perfect :: [Int]
perfect = [i | i<-[1..1], i == sum (divisors i)]



This should be a little faster , as sum will fuse,

perfect :: [Int]
perfect = [i | i<-[1..1], i == sum' (divisors i)]
where sum' = foldr (+) 0


sum' did not help. Times are about the same with Int type.

Peter.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe