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

2007-10-30 Thread Jules Bean

Isaac Dupree wrote:
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




It is really annoying, and it is an astoundingly old bug in firefox. 
Apparently it's very hard to fix due to annoying details of the firefox 
architecture.


It would be simplest for everyone if haskell.org was prepared to send 
out the files as text/plain (even though this is the wrong mime type), 
as I believe it used to do.


The browser plugins can help, though.

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


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

2007-10-30 Thread Josef Svenningsson
On 10/29/07, Bulat Ziganshin [EMAIL PROTECTED] wrote:
 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

Indeed.

avg4:
880,935,612 bytes allocated in the heap
319,064,404 bytes copied during GC (scavenged)
318,965,812 bytes copied during GC (not scavenged)
201,080,832 bytes maximum residency (9 sample(s))

   1681 collections in generation 0 (  1.67s)
  9 collections in generation 1 ( 13.62s)

avgP:
1,761,224,604 bytes allocated in the heap
714,644 bytes copied during GC (scavenged)
593,184 bytes copied during GC (not scavenged)
184,320 bytes maximum residency (2 sample(s))

   1908 collections in generation 0 (  0.04s)
  2 collections in generation 1 (  0.00s)

Allocation is cheap, copying expensive.

All the best,

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


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

2007-10-30 Thread Bulat Ziganshin
Hello Josef,

Tuesday, October 30, 2007, 4:13:04 PM, you wrote:

 201,080,832 bytes maximum residency (9 sample(s))
1681 collections in generation 0 (  1.67s)
   9 collections in generation 1 ( 13.62s)

 184,320 bytes maximum residency (2 sample(s))
1908 collections in generation 0 (  0.04s)
   2 collections in generation 1 (  0.00s)

 Allocation is cheap, copying expensive.

not copying itself, but generation-1 garbage collections. while g-0
collection scans 256kb which lives in CPU cache, g-1 collection scans
entire 100-200 mb of data that is very slow. try to use -H1g option,
though :)

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Letting the darcs test fail, if QuickCheck tests fail

2007-10-30 Thread Henning Thielemann

When following the description on
 
http://www.haskell.org/haskellwiki/How_to_write_a_Haskell_program#Add_some_automated_testing:_QuickCheck
  then darcs will run the QuickCheck tests on each 'darcs record', but the
new patch is also accepted by darcs if one of the tests fail. What is the
most simple way to let 'darcs record' fail, when a QuickCheck test fails?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Letting the darcs test fail, if QuickCheck tests fail

2007-10-30 Thread Josef Svenningsson
On 10/30/07, Henning Thielemann [EMAIL PROTECTED] wrote:

 When following the description on
  
 http://www.haskell.org/haskellwiki/How_to_write_a_Haskell_program#Add_some_automated_testing:_QuickCheck
   then darcs will run the QuickCheck tests on each 'darcs record', but the
 new patch is also accepted by darcs if one of the tests fail. What is the
 most simple way to let 'darcs record' fail, when a QuickCheck test fails?

The same thing bit me when I prepared a package recently. The way I
solved it was to call the function quickCheck' instead of test. It
returns a boolean indicating if the test was successful or not. If
it's false I call exitWithFailure. I posted some code to the wikibook:
http://en.wikibooks.org/wiki/Talk:Haskell/Packaging

Note that quickCheck' is only available in QuickCheck 2.

All the best,

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


Re: [Haskell-cafe] Letting the darcs test fail, if QuickCheck tests fail

2007-10-30 Thread David Roundy
On Tue, Oct 30, 2007 at 05:24:21PM +0100, Henning Thielemann wrote:
 When following the description on
  
 http://www.haskell.org/haskellwiki/How_to_write_a_Haskell_program#Add_some_automated_testing:_QuickCheck
   then darcs will run the QuickCheck tests on each 'darcs record', but the
 new patch is also accepted by darcs if one of the tests fail. What is the
 most simple way to let 'darcs record' fail, when a QuickCheck test fails?

You can do this with QuickCheck 2 using quickCheck', but I don't know how
to do this with QuickCheck 1.  xmonad uses a function mytests, which I
guess is pretty much copied from the code of QuickCheck 1, with tracking of
errors added in.  It's ugly, but it's only a few dozen lines.

Another option would be to grep the output of the test suite to look for
failure.
-- 
David Roundy
Department of Physics
Oregon State University
___
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-30 Thread Richard Kelsall

Jules Bean wrote:

Isaac Dupree wrote:
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




It is really annoying, and it is an astoundingly old bug in firefox. 
Apparently it's very hard to fix due to annoying details of the firefox 
architecture.


It would be simplest for everyone if haskell.org was prepared to send 
out the files as text/plain (even though this is the wrong mime type), 
as I believe it used to do.

...

Yes, it does appear to be a bug in Firefox

https://bugzilla.mozilla.org/show_bug.cgi?id=57342

not to attempt to display text/x-haskell as if it were text/plain,
but to get really obsessive I'm not convinced text/plain is strictly
speaking the 'wrong' media-type if that's what the user-agent requests.
For example, my FireFox 1.5.0.5 says to the server it will Accept these
media-types

text/xml, application/xml, application/xhtml+xml, text/html; q=0.9,
text/plain; q=0.8,
image/png,*/*; q=0.5

This is in order of what it would most like to get back from the server.
The server then goes off and tries to find the best media-type for my
browser - it can supply different ones depending on what the browser
says it wants. By returning it as text/x-haskell the server has given
the resource to my browser in */* which is the least wanted media-type.
This is perfectly correct behaviour, but if the server was also capable
of providing the same thing as text/plain it would be better to give
this, or even better a pretty coloured text/html one if the server had
one available. I think the underlying file returned as text/x-haskell
or text/plain can be the exact same file assuming all x-haskell are
also plain.

Could be wrong, but that's my understanding of content negotiation.


Richard.

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


[Haskell-cafe] Strictness leak

2007-10-30 Thread Ketil Malde

Some time ago, I posted this code:

 countIO :: String - String - Int - [a] - IO [a]
 countIO msg post step xs = sequence $ map unsafeInterleaveIO ((blank  
 outmsg (0::Int)  c):cs)
where (c:cs) = ct 0 xs
  output   = hPutStr stderr
  blank= output ('\r':take 70 (repeat ' '))
  outmsg x = output ('\r':msg++show x)  hFlush stderr
  ct s ys = let (a,b) = splitAt (step-1) ys
next  = s+step
in case b of [b1] - map return a ++ [outmsg (s+step)  
 hPutStr stderr post  return b1]
 []   - map return (init a) ++ [outmsg 
 (s+length a)  hPutStr stderr post  return (last a)]
 _ - map return a ++ [outmsg s  return 
 (head b)] ++ ct next (tail b)

It wraps a list with IO operations, so that progress can be reported
while evaluating the list elements.  Unfortunately, there seems to be
a stricness leak here - and consequently, it does not work on an
infinite list. 

I'm not sure why this happens, can anybody else see it?

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strictness leak

2007-10-30 Thread Jeff Polakow
Hello,

  countIO :: String - String - Int - [a] - IO [a]
  countIO msg post step xs = sequence $ map unsafeInterleaveIO 
 ((blank  outmsg (0::Int)  c):cs)
 where (c:cs) = ct 0 xs
   output   = hPutStr stderr
   blank= output ('\r':take 70 (repeat ' '))
   outmsg x = output ('\r':msg++show x)  hFlush stderr
   ct s ys = let (a,b) = splitAt (step-1) ys
 next  = s+step
 in case b of [b1] - map return a ++ [outmsg 
 (s+step)  hPutStr stderr post  return b1]
  []   - map return (init a) ++ 
 [outmsg (s+length a)  hPutStr stderr post  return (last a)]
  _ - map return a ++ [outmsg s  
 return (head b)] ++ ct next (tail b)
 
 It wraps a list with IO operations, so that progress can be reported
 while evaluating the list elements.  Unfortunately, there seems to be
 a stricness leak here - and consequently, it does not work on an
 infinite list. 
 
Besides anything else, sequence will diverge on an infinite list. This can 
be seen directly from the type:

sequence :: Monad m = [m a] - m [a] 

It is necessary to compute all of the computations in the list before 
returning any of the pure resulting list.

-Jeff


---

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] Strictness leak

2007-10-30 Thread Emil Axelsson

You mean for the IO monad, right?

  take 10 $ execWriter $ sequence $ repeat $ tell ([3]::[Int])

/ Emil



On 10/30/2007 02:04 PM, Jeff Polakow wrote:


Hello,

   countIO :: String - String - Int - [a] - IO [a]
   countIO msg post step xs = sequence $ map unsafeInterleaveIO
  ((blank  outmsg (0::Int)  c):cs)
  where (c:cs) = ct 0 xs
output   = hPutStr stderr
blank= output ('\r':take 70 (repeat ' '))
outmsg x = output ('\r':msg++show x)  hFlush stderr
ct s ys = let (a,b) = splitAt (step-1) ys
  next  = s+step
  in case b of [b1] - map return a ++ [outmsg
  (s+step)  hPutStr stderr post  return b1]
   []   - map return (init a) ++
  [outmsg (s+length a)  hPutStr stderr post  return (last a)]
   _ - map return a ++ [outmsg s 
  return (head b)] ++ ct next (tail b)
 
  It wraps a list with IO operations, so that progress can be reported
  while evaluating the list elements.  Unfortunately, there seems to be
  a stricness leak here - and consequently, it does not work on an
  infinite list.
 
Besides anything else, sequence will diverge on an infinite list. This 
can be seen directly from the type:


sequence :: Monad m = [m a] - m [a]

It is necessary to compute all of the computations in the list before 
returning any of the pure resulting list.


-Jeff

---

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

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


[Haskell-cafe] Hugs running on cygwin

2007-10-30 Thread Galchin Vasili
Hello,

  When I was downloading and installing the cygwin tool set on my
laptop, I noticed that Hugs doesn't appear to be in the toolset. What would
it take to get Hugs running on top of cygwin? I guess the Hugs Makefile
would have to be modified to correctly link in any of the cygwin Unix
libraries.

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


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

2007-10-30 Thread Dan Piponi
Jerzy,

There is a simple framework for performing filtering operations on
images lazily: 
http://sigfpe.blogspot.com/2006/12/evaluating-cellular-automata-is.html
(Scroll down to the 2D example in the comments.)

2D digital filters lend themselves nicely to a comonadic framework
though you probably have to drop the comonads for operations other
than convolution type things. And you're right, doing this lazily at
the pixel level is expensive. However, if we replace pixels with
256x256 blocks, say, where the blocks themselves are strict but the
images are lazily made up of blocks, then we have the potential for a
nice and efficient image processing library that inherits its laziness
directly from Haskell.

On 10/30/07, [EMAIL PROTECTED]
[EMAIL PROTECTED] wrote:
 Dan Piponi adds to a short exchange:

  jerzy.karczmarczuk:
  [iso-8859-1] Bj�rn Wikstr�m writes:
 
   Hi! I have lots and lots of images (jpegs) that I would like to 
   manipulate
   and shrink (in size). They are around 5 Mb big, so I thought this would
   be a good Haskell project since it's a lazy evaluating language.
  ...
  I must say that I don't see much use of laziness here.

  Laziness plays a big role in real world image processing. Typically,
  in applications like Apple's Shake, you build a dataflow
  representation of the image processing operations you wish to perform,
  and the final result is computed lazily so as to reduce the amount of
  computation. For example, if you blur an image, and then zoom in on
  the top left corner, then only the top left corner will be loaded up
  from the original image (assuming your image file format supports
  tiled access). You still work on tiles or scan-lines, rather than
  individual pixels, so the laziness has a 'coarse' granularity.
 
  But I'm not sure if this is what the original poster was talking about.

 I am neither...
 Still, Dan, I think that there is quite a difference between incremental
 processing of signals, and images, etc., and the *lazy evaluation* of
 them. Of course, a stream is consumed as economically as it can, but
 not less. If you filter an image (shrinking, so some low-pass MUST be
 done), a pixel must be loaded with its neighbourhood, which means *some*
 scan lines.
 With a JPEG this means that a 8x8 block should be loaded also with its
 vicinity. But would you suggest that individual pixel processors should
 be lazy? It would be useless, and probably resulting in some penalties.

 So, the laziness of Haskell for me here is less than useful.
 Nw, the lazy *generation* of streams is another story...
 Generating music (low level, i.e. sound patterns) through lazy algorithms
 is quite interesting.

 Jerzy Karczmarczuk


 ___
 Haskell mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell

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


Re: [Haskell-cafe] Type inference problem with division (/)

2007-10-30 Thread Tim Chevalier
On 10/30/07, noa [EMAIL PROTECTED] wrote:

 Hi!

 I have the following function:

 theRemainder :: [String] - [String] - Double
 theRemainder xs xt = sum( map additional (unique xs) )
 where
 additional x = poccur * (inf [ppos,pneg]) --inf takes [Double]
 where
 xsxt = zip xs xt
 pi = countPos xr -- countPos returns an Int
 ni = (length xr) - pi
 len = length xs
 len2 = length xr
 ppos = pi/len2 -- THESE ARE THE PROBLEM
 pneg = ni/len2 -- THESE ARE THE PROBLEM
 poccur = (pi+ni)/len
 xr = (filter ((\y - (fst y)==x)) (xsxt))

 And I am getting this error message with ghc:

 matrix.hs:54:31:
 Couldn't match expected type `Double' against inferred type `Int'
 In the expression: ppos
 In the first argument of `inf', namely `[ppos, pneg]'
 In the second argument of `(*)', namely `(inf [ppos, pneg])'

 How can I change the declaration of ppos nad pneg so they are treated as
 Double for the inf function?


ppos = pi/len2; pi and len2 are both Ints, so dividing them gives you
an Int. To convert to a Double, write ppos = fromIntegral (pi/len2).
(Type :t fromIntegral in ghci to see what else fromIntegral can be
used for.)

Cheers,
Tim

-- 
Tim Chevalier * catamorphism.org * Often in error, never in doubt
After three days without programming, life becomes meaningless.  --
James Geoffrey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type inference problem with division (/)

2007-10-30 Thread Felipe Lessa
On 10/30/07, Tim Chevalier [EMAIL PROTECTED] wrote:
 ppos = pi/len2; pi and len2 are both Ints, so dividing them gives you
 an Int. To convert to a Double, write ppos = fromIntegral (pi/len2).
 (Type :t fromIntegral in ghci to see what else fromIntegral can be
 used for.)

You mean pi / fromIntegral len2, right?

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


[Haskell-cafe] Type inference problem with division (/)

2007-10-30 Thread noa

Hi!

I have the following function:

theRemainder :: [String] - [String] - Double
theRemainder xs xt = sum( map additional (unique xs) )
where
additional x = poccur * (inf [ppos,pneg]) --inf takes [Double]
where
xsxt = zip xs xt
pi = countPos xr -- countPos returns an Int
ni = (length xr) - pi
len = length xs
len2 = length xr
ppos = pi/len2 -- THESE ARE THE PROBLEM
pneg = ni/len2 -- THESE ARE THE PROBLEM
poccur = (pi+ni)/len
xr = (filter ((\y - (fst y)==x)) (xsxt))

And I am getting this error message with ghc:

matrix.hs:54:31:
Couldn't match expected type `Double' against inferred type `Int'
In the expression: ppos
In the first argument of `inf', namely `[ppos, pneg]'
In the second argument of `(*)', namely `(inf [ppos, pneg])'

How can I change the declaration of ppos nad pneg so they are treated as
Double for the inf function?

Cheers,
Nick
-- 
View this message in context: 
http://www.nabble.com/Type-inference-problem-with-division-%28-%29-tf4722111.html#a13500475
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Type inference problem with division (/)

2007-10-30 Thread Shachaf Ben-Kiki
On 10/30/07, Tim Chevalier [EMAIL PROTECTED] wrote:
 On 10/30/07, noa [EMAIL PROTECTED] wrote:
 
  Hi!
 
  I have the following function:
 
  theRemainder :: [String] - [String] - Double
  theRemainder xs xt = sum( map additional (unique xs) )
  where
  additional x = poccur * (inf [ppos,pneg]) --inf takes [Double]
  where
  xsxt = zip xs xt
  pi = countPos xr -- countPos returns an Int
  ni = (length xr) - pi
  len = length xs
  len2 = length xr
  ppos = pi/len2 -- THESE ARE THE PROBLEM
  pneg = ni/len2 -- THESE ARE THE PROBLEM
  poccur = (pi+ni)/len
  xr = (filter ((\y - (fst y)==x)) (xsxt))
 
  And I am getting this error message with ghc:
 
  matrix.hs:54:31:
  Couldn't match expected type `Double' against inferred type `Int'
  In the expression: ppos
  In the first argument of `inf', namely `[ppos, pneg]'
  In the second argument of `(*)', namely `(inf [ppos, pneg])'
 
  How can I change the declaration of ppos nad pneg so they are treated as
  Double for the inf function?
 

 ppos = pi/len2; pi and len2 are both Ints, so dividing them gives you
 an Int. To convert to a Double, write ppos = fromIntegral (pi/len2).
 (Type :t fromIntegral in ghci to see what else fromIntegral can be
 used for.)

You can't divide Ints with (/) at all -- they aren't Fractional.
You'll probably want to either fromIntegral both pi and len2 or use
div for integer division.

(Also, pi is a bit of a confusing name; you may want to consider using
another one.)

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


[Haskell-cafe] help needed packaging curl bindings

2007-10-30 Thread brad clawsie
i have decided to take on the task of packaging-up (for hackage) and
documenting the curl bindings as available here:

http://code.haskell.org/curl/

if the originators of this code are reading this and do not wish me to
proceed please say so, i won't be offended

otherwise i was wondering if people had good examples to point me to
for providing the cross-platform support needed for a FFI-based module
such as this. i have made the necessary changes to compile the code on
freebsd, but for other platforms i am not sure at all, particularly
non-unix style platforms like windows.

my guess is that providing cross-platform support requires autoconf
etc prior to the hackage build process (?)

any info/references appreciated
thanks
brad


pgpgos8fJXkpz.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strictness leak

2007-10-30 Thread Jeff Polakow
I forgot to send this reponse to haskell-cafe earlier...

Hello,

 You mean for the IO monad, right?
 
Sorry. I meant divergence is unavoidable for any strict Monad, such as IO. 


However, sequence will always compute over the entire list; if the 
resulting computation itself is lazy then the result can be inspected 
lazily.

take 10 $ execWriter $ sequence $ repeat $ tell ([3]::[Int])
 
This is a good example. Note that the computation of sequence itself is 
infinite.

snd $ runWriter $ sequence (repeat $ tell [3]) = return . take 10

will result in an infinite list, but

fst $ runWriter $ sequence (repeat $ tell [3]) = return . take 10

will return a 10 element list.

-Jeff


---

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