Re: [Haskell-cafe] my knucleotide fast on 64 bit but extremely slow on 32 bit?

2013-03-28 Thread Don Stewart
Int64 is emulated on 32 bit. So it is not as efficient by a long shot.

On Thursday, 28 March 2013, Branimir Maksimovic wrote:

 I have posted previous knucleotide program, it is fast on 64 bit but
 very slow on 32 bit.
 I cannot install 32 bit ghc to test it so I can only guess is that
 cause is use of Int64 for hash and HashMap array indexing.
 What bothers me is that it that much slower , and I guess
 that array indexing of 64 bit int where native index is 32 bit
 is culprit.
 Am I right? If I make Int index of array it will be fast on
 32 bit platform too?
 I cannot imagine that hashing to 64 bit int is culprit rather
 array indexing as I guess that every array access
 requires indirect access on 32 bit platform?

 64 bit :

 http://benchmarksgame.alioth.debian.org/u64q/program.php?test=knucleotidelang=ghcid=1
 19.80 secs
 32 bit:

 http://benchmarksgame.alioth.debian.org/u32q/program.php?test=knucleotidelang=ghcid=1
 91.01 secs ;(

 I really like Haskell, but Im frustrated as how inpredictable it is.
 Im programming from 1983' but found Haskell as much more difficult
 to program efficiently than C++.
 In C++ whatever lousy program I write it performs decently,
 but not so in Haskell. It requires much deeper knowledge than
 c++.




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


Re: [Haskell-cafe] Enumerating functions at runtime

2013-03-24 Thread Don Stewart
All the info is in the .hi files

On Sunday, 24 March 2013, Brent Yorgey wrote:

 On Sat, Mar 23, 2013 at 08:26:52PM -0700, Luke Evans wrote:
  I'm curious about using Haskell for metaprogramming.
 
  It looks like I can dynamically compile, load and run some Haskell with
 the plugins package.  Actually I've briefly tried this and it seems to work
 for some simple cases at least.
  Now I would like to be able to enumerate precompiled public functions in
 modules that I might use as building blocks in such dynamic compilation.
  So far I'm not seeing anything that does this directly.
  Can anyone provide some pointers?
 
  If it's just not possible to introspect on compiled modules, then I
 suppose I could use external metadata of my own, or even perhaps haddock
 info if it exists, to attempt to generate this info.  Clearly though,
 that's nowhere near as good as extracting the info from something the
 compiler built directly.

 I have no idea how it works, but I'm pretty sure yi does this ---
 e.g. if you hit M-x (when in emacs emulation mode) and then
 tab-complete, you see a list of all the available functions.  Maybe
 you want to take a look at the yi source code and see how they do it.

 -Brent

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org javascript:;
 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] Streaming bytes and performance

2013-03-19 Thread Don Stewart
Just for fun. Here's some improvements. about 6x faster.
I'd be interested to see what io-streams could do on this.

Using a 250M test file.

-- strict state monad and bang patterns on the uncons and accumulator
argument:

$ time ./A
4166680
./A  8.42s user 0.57s system 99% cpu 9.037 total

-- just write a loop

$ time ./A
4166680
./A  3.84s user 0.26s system 99% cpu 4.121 total

-- switch to Int

$ time ./A
4166680
./A  1.89s user 0.23s system 99% cpu 2.134 total

-- custom isSpace function

$ time ./A
4166680
./A  1.56s user 0.24s system 99% cpu 1.808 total

-- mmap IO

$ time ./A
4166680
./A  1.54s user 0.09s system 99% cpu 1.636 total

Here's the final program:


{-# LANGUAGE BangPatterns #-}

import qualified Data.ByteStringas S
import qualified Data.ByteString.Lazy.Char8 as L
import System.IO.Posix.MMap.Lazy

main = do
f - unsafeMMapFile test.txt
print $ go 0 f
  where
go :: Int - L.ByteString - Int
go !a !s = case L.uncons s of
Nothing - a
Just (x,xs) | isSpaceChar8 x - go (a+1) xs
| otherwise  - go a xs

isSpaceChar8 c = c == '\n'|| c == ' '
{-# INLINE isSpaceChar8 #-}


On Mon, Mar 18, 2013 at 8:53 AM, Konstantin Litvinenko 
to.darkan...@gmail.com wrote:

 Hi All!

 I tune my toy project for performance and hit the wall on simple, in
 imperative world, task. Here is the code that model what I'm trying to
 achieve

 import qualified Data.ByteString.Lazy as L
 import Data.Word8(isSpace)
 import Data.Word
 import Control.Monad.State

 type Stream = State L.ByteString

 get_byte :: Stream (Maybe Word8)
 get_byte = do
 s - get
 case L.uncons s of
 Nothing - return Nothing
 Just (x, xs) - put xs  return (Just x)

 main = do
 f - L.readFile test.txt
 let r = evalState count_spaces f
 print r
   where
 count_spaces = go 0
   where
 go a = do
 x - get_byte
 case x of
 Just x' -  if isSpace x' then go (a + 1) else go a
 Nothing - return a

 It takes the file and count spaces, in imperative way, consuming bytes one
 by one. The problem is: How to rewrite this to get rid of constant
 allocation of state but still working with stream of bytes? I can rewrite
 this as one-liner L.foldl, but that doesn't help me in any way to optimize
 my toy project where all algorithms build upon consuming stream of bytes.

 PS. My main lang is C++ over 10 years and I only learn Haskell :)


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://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] Streaming bytes and performance

2013-03-19 Thread Don Stewart
Oh, I forgot the technique of inlining the lazy bytestring chunks, and
processing each chunk seperately.

$ time ./fast
4166680
./fast  1.25s user 0.07s system 99% cpu 1.325 total

Essentially inline Lazy.foldlChunks and specializes is (the inliner should
really get that).
And now we have a nice unboxed inner loop, which llvm might spot:

$ ghc -O2 -funbox-strict-fields fast.hs  --make -fllvm
$ time ./fast
4166680
./fast  1.07s user 0.06s system 98% cpu *1.146 total*

So about 8x faster. Waiting for some non-lazy bytestring benchmarks... :)

{-# LANGUAGE BangPatterns #-}

import Data.ByteString.Internal
import Data.ByteString.Unsafe
import qualified Data.ByteString.Char8  as S
import qualified Data.ByteString.Lazy.Char8 as L
import qualified Data.ByteString.Lazy.Internal as L
import System.IO.Posix.MMap.Lazy

main = do
f - unsafeMMapFile test.txt
print . new 0 $ L.toChunks f

new :: Int - [ByteString] - Int
new i [] = i
new i (x:xs) = new (add i x) xs

-- jump into the fast path
{-# INLINE add #-}
add :: Int - ByteString - Int
add !i !s | S.null s   = i
  | isSpace' x = add (i+1) xs
  | otherwise  = add i xs
  where T x xs = uncons s

data T = T !Char ByteString

uncons s = T (w2c (unsafeHead s)) (unsafeTail s)

isSpace' c = c == '\n'|| c == ' '
{-# INLINE isSpace' #-}




On Tue, Mar 19, 2013 at 7:36 PM, Don Stewart don...@gmail.com wrote:

 Just for fun. Here's some improvements. about 6x faster.
 I'd be interested to see what io-streams could do on this.

 Using a 250M test file.

 -- strict state monad and bang patterns on the uncons and accumulator
 argument:

 $ time ./A
 4166680
 ./A  8.42s user 0.57s system 99% cpu 9.037 total

 -- just write a loop

 $ time ./A
 4166680
 ./A  3.84s user 0.26s system 99% cpu 4.121 total

 -- switch to Int

 $ time ./A
 4166680
 ./A  1.89s user 0.23s system 99% cpu 2.134 total

 -- custom isSpace function

 $ time ./A
 4166680
 ./A  1.56s user 0.24s system 99% cpu 1.808 total

 -- mmap IO

 $ time ./A
 4166680
 ./A  1.54s user 0.09s system 99% cpu 1.636 total

 Here's the final program:


 {-# LANGUAGE BangPatterns #-}

 import qualified Data.ByteStringas S
 import qualified Data.ByteString.Lazy.Char8 as L
 import System.IO.Posix.MMap.Lazy

 main = do
 f - unsafeMMapFile test.txt
 print $ go 0 f
   where
 go :: Int - L.ByteString - Int
 go !a !s = case L.uncons s of
 Nothing - a
 Just (x,xs) | isSpaceChar8 x - go (a+1) xs
 | otherwise  - go a xs

 isSpaceChar8 c = c == '\n'|| c == ' '
 {-# INLINE isSpaceChar8 #-}


 On Mon, Mar 18, 2013 at 8:53 AM, Konstantin Litvinenko 
 to.darkan...@gmail.com wrote:

 Hi All!

 I tune my toy project for performance and hit the wall on simple, in
 imperative world, task. Here is the code that model what I'm trying to
 achieve

 import qualified Data.ByteString.Lazy as L
 import Data.Word8(isSpace)
 import Data.Word
 import Control.Monad.State

 type Stream = State L.ByteString

 get_byte :: Stream (Maybe Word8)
 get_byte = do
 s - get
 case L.uncons s of
 Nothing - return Nothing
 Just (x, xs) - put xs  return (Just x)

 main = do
 f - L.readFile test.txt
 let r = evalState count_spaces f
 print r
   where
 count_spaces = go 0
   where
 go a = do
 x - get_byte
 case x of
 Just x' -  if isSpace x' then go (a + 1) else go a
 Nothing - return a

 It takes the file and count spaces, in imperative way, consuming bytes
 one by one. The problem is: How to rewrite this to get rid of constant
 allocation of state but still working with stream of bytes? I can rewrite
 this as one-liner L.foldl, but that doesn't help me in any way to optimize
 my toy project where all algorithms build upon consuming stream of bytes.

 PS. My main lang is C++ over 10 years and I only learn Haskell :)


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://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] Streaming bytes and performance

2013-03-19 Thread Don Stewart
This isn't a valid entry -- it uses strict IO (so allocates O(n) space) and
reads from standard input, which pretty much swamps the interesting
constant factors with buffered IO overhead.

Compare your program (made lazy) on lazy bytestrings using file IO:

import Prelude hiding ( readFile, foldl )
import Data.ByteString.Lazy.Char8

countSpace :: Int - Char - Int
countSpace i c | c == ' ' || c == '\n' = i + 1
   | otherwise = i

main :: IO ()
main = readFile test.txt = print . foldl countSpace 0


Against my earlier optimized one (that manually specializes and does other
tricks).


$ time ./C
4166680
./C  1.49s user 0.42s system 82% cpu 2.326 total

$ time ./fast
4166680
./fast  1.05s user 0.11s system 96% cpu 1.201 total


The optimized one is twice as fast. You can write the same program on lists
, and it also runs in constant space but completes 32s instead  of 1.3

Constant factors matter.

On Tue, Mar 19, 2013 at 9:03 PM, Peter Simons sim...@cryp.to wrote:

 Don Stewart don...@gmail.com writes:

   Here's the final program: [...]

 Here is a version of the program that is just as fast:

   import Prelude hiding ( getContents, foldl )
   import Data.ByteString.Char8

   countSpace :: Int - Char - Int
   countSpace i c | c == ' ' || c == '\n' = i + 1
  | otherwise = i

   main :: IO ()
   main = getContents = print . foldl countSpace 0

 Generally speaking, I/O performance is not about fancy low-level system
 features, it's about having a proper evaluation order:

  | $ ghc --make -O2 -funbox-strict-fields test1  time ./test1
  | 37627064
  |
  | real 0m0.381s
  | user 0m0.356s
  | sys  0m0.023s

 Versus:

  | $ ghc --make -O2 -funbox-strict-fields test2  time ./test2 test.txt
  | Linking test2 ...
  | 37627064
  |
  | real 0m0.383s
  | user 0m0.316s
  | sys  0m0.065s

 Using this input file stored in /dev/shm:

  | $ ls -l test.txt
  | -rw-r--r-- 1 simons users 208745650 Mar 19 21:40 test.txt

 Take care,
 Peter


 ___
 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] Streaming bytes and performance

2013-03-19 Thread Don Stewart
Oh I see what you're doing ... Using this input file stored in /dev/shm

So not measuring the IO performance at all. :)
On Mar 19, 2013 9:27 PM, Peter Simons sim...@cryp.to wrote:

 Hi Don,

   Compare your program (made lazy) on lazy bytestrings using file IO:
 [...]

 if I make those changes, the program runs even faster than before:

   module Main ( main ) where

   import Prelude hiding ( foldl, readFile )
   import Data.ByteString.Lazy.Char8

   countSpace :: Int - Char - Int
   countSpace i c | c == ' ' || c == '\n' = i + 1
  | otherwise = i

   main :: IO ()
   main = readFile test.txt = print . foldl countSpace 0

 This gives

  | $ ghc --make -O2 -funbox-strict-fields test1  time ./test1
  | 37627064
  |
  | real0m0.375s
  | user0m0.346s
  | sys 0m0.028s

 versus:

  | $ ghc --make -O2 -funbox-strict-fields test2  time ./test2
  | 37627064
  |
  | real0m0.324s
  | user0m0.299s
  | sys 0m0.024s

 Whether getFile or getContents is used doesn't seem to make difference.

 Take care,
 Peter

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


Re: [Haskell-cafe] Streaming bytes and performance

2013-03-19 Thread Don Stewart
I guess the optimizations that went into making lazy bytestring IO fast (on
disks) are increasingly irrelevant as SSDs take over.
On Mar 19, 2013 9:49 PM, Peter Simons sim...@cryp.to wrote:

 Hi Don,

   Using this input file stored in /dev/shm
  
   So not measuring the IO performance at all. :)

 of course the program measures I/O performance. It just doesn't measure
 the speed of the disk.

 Anyway, a highly optimized benchmark such as the one you posted is
 eventually going to beat one that's not as highly optimized. I think
 no-one disputes that fact.

 I was merely trying to point out that a program which encodes its
 evaluation order properly is going to be reasonably fast without any
 further optimizations.

 Take care,
 Peter

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


Re: [Haskell-cafe] ANNOUNCE: Start Ajhc project with forking jhc.

2013-03-06 Thread Don Stewart
Very cool!
On Mar 6, 2013 12:53 PM, Kiwamu Okabe kiw...@debian.or.jp wrote:

 Hi all.

 I am a user of jhc Haskell compiler.
 Jhc can compile Haskell code to micro arch such as Cortex-M3.
 I have written LED blinking demo for Cortex-M3 with jhc.
 Very fun!

   https://github.com/ajhc/demo-cortex-m3
   http://www.youtube.com/watch?v=3R9sogReVHg

 And I created many patches for jhc.
 But...I think that the upstream author of jhc, John Meacham,
 can't pull the contribution speedy, because he is too busy.
 It's difficult that maintain many patches without any repositories,
 for me.

 Then, I have decided to fork jhc, named Ajhc.
 # pain full...

   http://ajhc.github.com/

 I will feedback Ajhc's big changes to jhc mailing list.
 Or I am so happy if John joins Ajhc project.

 Regards,
 --
 Kiwamu Okabe

 ___
 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] translating recursively defined sequence

2013-03-05 Thread Don Stewart
Isn't that already valid Haskell? :)

(remove the underscore).
On Mar 5, 2013 5:21 AM, Christopher Howard 
christopher.how...@frigidcode.com wrote:

 Hi. My Haskell is (sadly) getting a bit rusty. I was wondering what
 would be the most straightforward and easily followed procedure for
 translating a recursively defined sequence into a Haskell function. For
 example, this one from a homework assignment.

 quote:
 
 a_1 = 10
 a_(k+1) = (1/5) * (a_k)**2
 

 (The underscore is meant to represent subscripting what follows it.)

 --
 frigidcode.com


 ___
 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] Concurrency performance problem

2013-03-04 Thread Don Stewart
Depends on your code...
On Mar 4, 2013 6:10 PM, Łukasz Dąbek sznu...@gmail.com wrote:

 Hello Cafe!

 I have a problem with following code: http://hpaste.org/83460. It is a
 simple Monte Carlo integration. The problem is that when I run my
 program with +RTS -N1 I get:
 Multi
 693204.039020917 8.620632s
 Single
 693204.039020917 8.574839s
 End

 And with +RTS -N4 (I have four CPU cores):
 Multi
 693204.0390209169 11.877143s
 Single
 693204.039020917 11.399888s
 End

 I have two questions:
  1) Why performance decreases when I add more cores for my program?
  2) Why performance of single threaded integration also changes with
 number of cores?

 Thanks for all answers,
 Łukasz Dąbek.

 ___
 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] Concurrency performance problem

2013-03-04 Thread Don Stewart
Apologies, didn't see the link on my phone :)

As the comment on the link shows, youre accidentally migrating unevaluated
work to the main thread, hence no speedup.

Be very careful with evaluation strategies (esp. lazy expressions) around
MVar and TVar points. Its too easy to put a thunk in one.

The strict-concurrency package is one attempt to invert the conventional
lazy box, to better match thge most common case.
On Mar 4, 2013 7:25 PM, Łukasz Dąbek sznu...@gmail.com wrote:

 What do you exactly mean? I have included link to full source listing:
 http://hpaste.org/83460.

 --
 Łukasz Dąbek

 2013/3/4 Don Stewart don...@gmail.com:
  Depends on your code...
 
  On Mar 4, 2013 6:10 PM, Łukasz Dąbek sznu...@gmail.com wrote:
 
  Hello Cafe!
 
  I have a problem with following code: http://hpaste.org/83460. It is a
  simple Monte Carlo integration. The problem is that when I run my
  program with +RTS -N1 I get:
  Multi
  693204.039020917 8.620632s
  Single
  693204.039020917 8.574839s
  End
 
  And with +RTS -N4 (I have four CPU cores):
  Multi
  693204.0390209169 11.877143s
  Single
  693204.039020917 11.399888s
  End
 
  I have two questions:
   1) Why performance decreases when I add more cores for my program?
   2) Why performance of single threaded integration also changes with
  number of cores?
 
  Thanks for all answers,
  Łukasz Dąbek.
 
  ___
  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] How does one create an input handle bound to a string instead of a file?

2013-02-27 Thread Don Stewart
I don't think that's right - Simon's buffer class rewrite should have made
this possible, I think.

http://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/GHC-IO-BufferedIO.html
On Feb 27, 2013 10:52 PM, Gregory Collins g...@gregorycollins.net wrote:

 On Wed, Feb 27, 2013 at 9:38 PM, John D. Ramsdell ramsde...@gmail.comwrote:

 How does one create a value of type System.IO.Handle for reading that
 takes its input from a string instead of a file?  I'm looking for the
 equivalent of java.io.StringReader in Java.  Thanks in advance.


 You can't. There are several libraries that purport to provide better
 interfaces for doing IO in Haskell, like conduit, pipes, enumerator, and my
 own io-streams library (http://github.com/snapframework/io-streams, soon
 to be released). You could try one of those.

 G
 --
 Gregory Collins g...@gregorycollins.net

 ___
 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] ANN: lazy-csv - the fastest and most space-efficient parser for CSV

2013-02-25 Thread Don Stewart
Cassava is quite new, but has the same goals as lazy-csv.

Its about a year old now -
http://blog.johantibell.com/2012/08/a-new-fast-and-easy-to-use-csv-library.html

I know Johan has been working on the benchmarks of late - it would be very
good to know how the two compare in features
On Feb 25, 2013 11:23 AM, Malcolm Wallace malcolm.wall...@me.com wrote:


 On 25 Feb 2013, at 11:14, Oliver Charles wrote:

  Obvious question: How does this compare to cassava? Especially cassava's
 Data.CSV.Incremental module? I specifically ask because you mention that
 it's  It is lazier, faster, more space-efficient, and more flexible in its
 treatment of errors, than any other extant Haskell CSV library on Hackage
 but there is no mention of cassava in the website.

 Simple answer - I have never heard of cassava, and suspect it did not
 exist when I first did the benchmarking. I'd be happy to re-do my
 performance comparison, including cassava and any other recent-ish CSV
 libraries, if I can find them.

 Regards,
 Malcolm
 ___
 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] Thunks and GHC pessimisation

2013-02-24 Thread Don Stewart
In toy examples like this it will be generally hard to convince GHC not to
just collapse your program down to a constant, when you're turning up the
optimization level.

In particular, you are implying -ffull-laziness with -O (or -O2), which can
increase sharing.

 GHC doesn't implement complete full-laziness. When optimisation in on,
and -fno-full-laziness is not  given, *some transformations that increase
sharing are performed, such as extracting repeated computations from a loop*.
These are the same transformations that a fully lazy implementation would
do, the difference is that GHC doesn't consistently apply full-laziness, so
don't rely on it.

http://www.haskell.org/ghc/docs/latest/html/users_guide/options-optimise.html

If you explicitly rely on this not happening, turn it off:

$ ghc -O2 -fno-full-laziness --make A.hs -rtsopts -fforce-recomp
[1 of 1] Compiling Main ( A.hs, A.o )
Linking A ...

$ time ./A +RTS -M750k
(5050,5050)
./A +RTS -M750k  0.06s user 0.00s system 97% cpu 0.069 total

A 750k heap should be enough for anyone :)

-- Don

On Sun, Feb 24, 2013 at 5:49 PM, Tom Ellis 
tom-lists-haskell-cafe-2...@jaguarpaw.co.uk wrote:

 To avoid retaining a large lazy data structure in memory it is useful to
 hide it behind a function call.  Below, many is used twice.  It is hidden
 behind a function call so it can be garbage collected between uses.  That's
 good.  When compiling with -O it seems that GHC 7.4.1 decides to keep it
 in memory anyway.  That's bad.  (I can't read core so I don't know exactly
 what's going on).  Replacing one of the many in twice with
 different_many makes everything fine again.

 Is this considered a bug in GHC?  Is it a known bug?  It is incredibly
 concerning that GHC would perform this kind of pessimisation.

 Tom


 % cat thunkfail.hs
 {-# OPTIONS_GHC -fno-warn-unused-binds #-}

 import Data.List

 million :: Int
 million = 10 ^ (6 :: Int)

 many :: () - [Int]
 many () = [1..million]

 different_many :: () - [Int]
 different_many () = [1..million]

 twice :: (Int, Int)
 twice = (foldl' (+) 0 (many ()), foldl' (+) 0 (many ()))

 main :: IO ()
 main = print twice

 % ghc -fforce-recomp -Wall -Werror -rtsopts thunkfail.hs  ./thunkfail
 +RTS -M5M
 [1 of 1] Compiling Main ( thunkfail.hs, thunkfail.o )
 Linking thunkfail ...
 (1784293664,1784293664)

 % ghc -O -fforce-recomp -Wall -Werror -rtsopts thunkfail.hs  ./thunkfail
 +RTS -M5M
 [1 of 1] Compiling Main ( thunkfail.hs, thunkfail.o )
 Linking thunkfail ...
 Heap exhausted;
 Current maximum heap size is 5242880 bytes (5 MB);
 use `+RTS -Msize' to increase it.

 ___
 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] Why is boxed mutable array so slow?

2012-12-01 Thread Don Stewart
The obvious difference between boxed and unboxed arrays is that the
boxed arrays are full of pointers to heap allocated objects. This
means you pay indirection to access the values, much more time in GC
spent chasing pointers (though card marking helps), and generally do
more allocation.

Compare the GC stats below, for

* Boxed vector: 88M bytes copied; 75% of time in GC, 0.472s
* Unboxed vector: 11k bytes copied, 1.3% of time in GC, 0.077s

So there's your main answer. The increased data density of unboxed
arrays also helps a too.

Now, you can help out  the GC signifcantly by hinting at how much
you're going to allocated in the youngest generation (see the
ghc-gc-tune app for a methodical approach to this, though it needs
updating to ghc 7 --
http://donsbot.wordpress.com/2010/07/05/ghc-gc-tune-tuning-haskell-gc-settings-for-fun-and-profit/
 and 
http://stackoverflow.com/questions/3171922/ghcs-rts-options-for-garbage-collection
).

Use the +RTS -A flag to set an initial youngest generation heap size
to the size of your array, and watch the GC cost disappear. For our
boxed vector, we'd use +RTS -A50M, resulting in:

* Boxed vector: 8k copied, 1% of time in GC, 0.157s

So not bad. 3x speedup through a RTS flag. -A is very useful if you
are working with boxed, mutable arrays.

For reference, there's a generic version below that specializes based
on the vector type parameter.

-

{-# LANGUAGE BangPatterns #-}

import System.CPUTime
import Text.Printf
import Data.Int
import Control.DeepSeq
import System.Mem

import qualified Data.Vector.Mutable as V
import qualified Data.Vector.Unboxed.Mutable as U
import qualified Data.Vector.Generic.Mutable as G

main :: IO()
main = do

--   (G.new n' :: IO (V.IOVector Int32)) = test' boxed vector
--   performGC
   (G.new n' :: IO (U.IOVector Int32)) = test' unboxed vector
   performGC

test' s a = do
putStrLn s
begin - getCPUTime
init'' a
partial_sum' a
end - getCPUTime
let diff = (fromIntegral (end - begin)) / (10**12)
last - G.read a (n'-1)
printf last %d seconds %.3f\n last (diff::Double)

n' :: Int
n' = 1000 * 1000

init'' !a = init 0 (n'-1)
  where
init :: Int - Int - IO ()
init !k !n
| k  n = return ()
| otherwise = do
let !x = fromIntegral $ k + k `div` 3
G.write a k x
init (k+1) n



partial_sum' !a = do
k - G.read a 0
ps 1 (n'-1) k
  where
ps :: Int - Int - Int32 - IO ()
ps i n s
| i  n = return ()
| otherwise = do
k - G.read a i
let !l = fromIntegral $ s + k
G.write a i l
ps (i+1) n l


-

$ time ./A +RTS -s
boxed vector
last 945735787 seconds 0.420
  40,121,448 bytes allocated in the heap
  88,355,272 bytes copied during GC
  24,036,456 bytes maximum residency (6 sample(s))
 380,632 bytes maximum slop
  54 MB total memory in use (0 MB lost due to fragmentation)

  %GC time  75.2%  (75.9% elapsed)

  Alloc rate359,655,602 bytes per MUT second

./A +RTS -s  0.40s user 0.07s system 98% cpu 0.475 total


$ time ./A +RTS -s
unboxed vector
last 945735787 seconds 0.080
   4,113,568 bytes allocated in the heap
  11,288 bytes copied during GC
   4,003,256 bytes maximum residency (3 sample(s))
 182,856 bytes maximum slop
   5 MB total memory in use (0 MB lost due to fragmentation)

  %GC time   1.3%  (1.3% elapsed)

  Alloc rate51,416,660 bytes per MUT second

./A +RTS -s  0.08s user 0.01s system 98% cpu 0.088 total


$ time ./A +RTS -A50M -s
boxed vector
last 945735787 seconds 0.127
  40,121,504 bytes allocated in the heap
   8,032 bytes copied during GC
  44,704 bytes maximum residency (2 sample(s))
  20,832 bytes maximum slop
  59 MB total memory in use (0 MB lost due to fragmentation)

  %GC time   1.0%  (1.0% elapsed)

  Productivity  97.4% of total user, 99.6% of total elapsed

./A +RTS -A50M -s  0.10s user 0.05s system 97% cpu 0.157 total



-


On Sat, Dec 1, 2012 at 11:09 AM, Branimir Maksimovic bm...@hotmail.com wrote:
 I have made benchmark test inspired by
 http://lemire.me/blog/archives/2012/07/23/is-cc-worth-it/

 What surprised me is that unboxed array is much faster than boxed array.
 Actually boxed array performance is on par with standard Haskell list
 which is very slow.
 All in all even unboxed array is about 10 times slower than Java version.
 I don't understand why is even unboxed array so slow.
 But! unboxed array consumes least amount of RAM.
 (warning, program consumes more than 3gb of ram)

  bmaxa@maxa:~/examples$ time ./Cumul
 boxed array
 last 262486571 seconds 4.972
 unboxed array
 last 262486571 seconds 0.776
 list
 last 262486571 seconds 6.812

 real0m13.086s
 user0m11.996s
 sys 0m1.080s

 

Re: [Haskell-cafe] Why is boxed mutable array so slow?

2012-12-01 Thread Don Stewart
Regarding when to use mutable arrays versus vectors, I would always
use vectors -- they optimize better, and have a better interface.

Also, I have updated and released a new version of the tool mentioned below.
You can get it on Hackage, updated to ghc 7 series.

http://hackage.haskell.org/package/ghc-gc-tune-0.3

For your boxed vector program, we get results that show a clear
performance peak with a -A of around 64M, about  the size of the
allocated array ...

http://i.imgur.com/dZ2Eo.png

Best settings for Running time:
0.16s:  +RTS -A67108864 -H1048576
0.16s:  +RTS -A67108864 -H2097152
0.16s:  +RTS -A67108864 -H8388608

E.g.

$ time ./A +RTS -A67M -H1M
boxed vector
last 945735787 seconds 0.123

-- Don

On Sat, Dec 1, 2012 at 12:20 PM, Don Stewart don...@gmail.com wrote:
 The obvious difference between boxed and unboxed arrays is that the
 boxed arrays are full of pointers to heap allocated objects. This
 means you pay indirection to access the values, much more time in GC
 spent chasing pointers (though card marking helps), and generally do
 more allocation.

 Compare the GC stats below, for

 * Boxed vector: 88M bytes copied; 75% of time in GC, 0.472s
 * Unboxed vector: 11k bytes copied, 1.3% of time in GC, 0.077s

 So there's your main answer. The increased data density of unboxed
 arrays also helps a too.

 Now, you can help out  the GC signifcantly by hinting at how much
 you're going to allocated in the youngest generation (see the
 ghc-gc-tune app for a methodical approach to this, though it needs
 updating to ghc 7 --
 http://donsbot.wordpress.com/2010/07/05/ghc-gc-tune-tuning-haskell-gc-settings-for-fun-and-profit/
  and 
 http://stackoverflow.com/questions/3171922/ghcs-rts-options-for-garbage-collection
 ).

 Use the +RTS -A flag to set an initial youngest generation heap size
 to the size of your array, and watch the GC cost disappear. For our
 boxed vector, we'd use +RTS -A50M, resulting in:

 * Boxed vector: 8k copied, 1% of time in GC, 0.157s

 So not bad. 3x speedup through a RTS flag. -A is very useful if you
 are working with boxed, mutable arrays.

 For reference, there's a generic version below that specializes based
 on the vector type parameter.

 -

 {-# LANGUAGE BangPatterns #-}

 import System.CPUTime
 import Text.Printf
 import Data.Int
 import Control.DeepSeq
 import System.Mem

 import qualified Data.Vector.Mutable as V
 import qualified Data.Vector.Unboxed.Mutable as U
 import qualified Data.Vector.Generic.Mutable as G

 main :: IO()
 main = do

 --   (G.new n' :: IO (V.IOVector Int32)) = test' boxed vector
 --   performGC
(G.new n' :: IO (U.IOVector Int32)) = test' unboxed vector
performGC

 test' s a = do
 putStrLn s
 begin - getCPUTime
 init'' a
 partial_sum' a
 end - getCPUTime
 let diff = (fromIntegral (end - begin)) / (10**12)
 last - G.read a (n'-1)
 printf last %d seconds %.3f\n last (diff::Double)

 n' :: Int
 n' = 1000 * 1000

 init'' !a = init 0 (n'-1)
   where
 init :: Int - Int - IO ()
 init !k !n
 | k  n = return ()
 | otherwise = do
 let !x = fromIntegral $ k + k `div` 3
 G.write a k x
 init (k+1) n



 partial_sum' !a = do
 k - G.read a 0
 ps 1 (n'-1) k
   where
 ps :: Int - Int - Int32 - IO ()
 ps i n s
 | i  n = return ()
 | otherwise = do
 k - G.read a i
 let !l = fromIntegral $ s + k
 G.write a i l
 ps (i+1) n l


 -

 $ time ./A +RTS -s
 boxed vector
 last 945735787 seconds 0.420
   40,121,448 bytes allocated in the heap
   88,355,272 bytes copied during GC
   24,036,456 bytes maximum residency (6 sample(s))
  380,632 bytes maximum slop
   54 MB total memory in use (0 MB lost due to fragmentation)

   %GC time  75.2%  (75.9% elapsed)

   Alloc rate359,655,602 bytes per MUT second

 ./A +RTS -s  0.40s user 0.07s system 98% cpu 0.475 total


 $ time ./A +RTS -s
 unboxed vector
 last 945735787 seconds 0.080
4,113,568 bytes allocated in the heap
   11,288 bytes copied during GC
4,003,256 bytes maximum residency (3 sample(s))
  182,856 bytes maximum slop
5 MB total memory in use (0 MB lost due to fragmentation)

   %GC time   1.3%  (1.3% elapsed)

   Alloc rate51,416,660 bytes per MUT second

 ./A +RTS -s  0.08s user 0.01s system 98% cpu 0.088 total


 $ time ./A +RTS -A50M -s
 boxed vector
 last 945735787 seconds 0.127
   40,121,504 bytes allocated in the heap
8,032 bytes copied during GC
   44,704 bytes maximum residency (2 sample(s))
   20,832 bytes maximum slop
   59 MB total memory in use (0 MB lost due to fragmentation)

   %GC time   1.0%  (1.0% elapsed)

   Productivity  97.4% of total user, 99.6% of total elapsed

 ./A +RTS -A50M -s  0.10s user

Re: [Haskell-cafe] size of Haskell Platform

2012-11-11 Thread Don Stewart
Hey Doug,

The process for adding new packages is specified here:

http://trac.haskell.org/haskell-platform/wiki/AddingPackages

The HP aims for comprehensive, general functionality. Things like
databases, graphics libraries and web servers are well in scope for
inclusion. It should grow.

Cheers,
  Don
On Nov 11, 2012 12:00 PM, Doug McIlroy d...@cs.dartmouth.edu wrote:

 This note is an offshoot of curl package broken in Windows,
 where this item appeared:

  Did you know that Strawberry Perl includes a cygwin gcc?
  ...
  Maybe Haskell Platform could do the same.

 The suggestion brought to mind a true-life parable: the pump
 station at Tok.  (Tok is the third corner--after Anchorage
 and Fairbanks--of Alaska's triangular core of long-distance
 highways.) When I visited Tok long ago, it was a village of
 several hundred souls, almost all of whom were employed by one
 government agency or another, principal among which were the
 highway department, the Alaska Communication Service and the
 pump station, which kept fuel flowing to Eielson Air Force Base.

 The mission of the station was to keep one pump running 24 hours
 a day. Most of the time, of course, the pump hummed along by
 itself. To assure that, there had to be a standby machine,
 an operator to watch over both, and a mechanic who could fix
 them if need be.  For such a lonely job it was deemed well to
 have two operators. And there had to be two operators for each
 of several shifts. A little redundancy on the mechanical side
 seemed wise, too.  The crew and their families, say nothing of
 the pumps themselves, needed to be housed, and the installation
 needed to be supplied with the necessities of life. (The nearest
 supermarket was in Fairbanks, 300 miles away.)  These needs
 demanded a motor pool and property maintenance cadre, whose
 very presence reinforced the need.

 Thus the support team to keep one pump going ballooned to about
 100 people--a chain reaction that barely avoided criticality.

 So it seems to be with Haskell Platform, which aims to include
 all you need to get up and running--an extensive set of
 standard libraries and utilities with full documentation. I
 get the impression that the Platform is bedeviled by the
 same prospect of almost unfettered growth.

 [One ominous sign: the description of the Haskell Platform
 at lambda.haskell.org/platform/doc/current/start.html suggests
 that one must join some mysterious Cabal, whose nature is
 hidden by a link to nowhere, simply to get started.]

 What principles guide the selection of components for all
 you need to get up and running?

 Doug McIlroy

 ___
 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] XMonad-screenshot

2012-07-25 Thread Don Stewart
Better sent to xmonad@

On Wednesday, July 25, 2012, Dmitry Malikov wrote:

 Hi.

 My friend Matvey Aksenov create some useful screen capturing utility for
 XMonad.
 https://github.com/supki/**xmonad-screenshothttps://github.com/supki/xmonad-screenshot

 It allows capturing all workspaces in single image. Also chosen workspaces
 could be filtered by some predicate.
 Result image could be filled with horizontal or vertical layout.

 Are there some other possible use cases for that utility?
 What are you expecting from the ideal screenshot module for XMonad?

 By the way, is there some another available screenshot utility specially
 for XMonad?

 --
 Best regards,
 dmitry malikov
 !


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://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] Are there arithmetic composition of functions?

2012-03-21 Thread Don Stewart
.

 On a side note, if we consider typeclasses as predicates on types, then
(especially with the extensions enabled) the type system looks extremely
like a obfuscated logic programming language.With existential types it even
starts to look like a first-order thereom prover.
 At present we can easily express different flavors of conjunction, but
expressing disjunction is hard. And that's why the Prelude can cause
problems here.



See
http://www.cse.chalmers.se/~hallgren/Papers/wm01.html

It gets even more fun with GADTs and, particularly, type families, which
are explicitly designed with type level proofs in mind

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


Re: [Haskell-cafe] strict version of Haskell - does it exist?

2012-01-29 Thread Don Stewart
Generally strict Haskell means using strict data types - vectors, arrays,
bytestrings, intmaps where required.

However, you usually don't want all code and data strict, all the time,
since laziness/on-demand eval is critical for deferring non-essential work.

Summary; -fstrict wouldn't magically make your code good. Using the right
balance of strict and lazy code, via the right choice of strict and lazy
types, however, often does.

Id be interested to know what choices were made in your log file case led
you into problems -- using something excessively lazy (like lazy lists) or
something excessively strict (like strict bytestrings) would both be
suboptimal for log analysis. A hybrid type like a lazy bytestring, would be
more appropriate.

On Sunday, January 29, 2012, Marc Weber marco-owe...@gmx.de wrote:
 A lot of work has been gone into GHC and its libraries.
 However for some use cases C is still preferred, for obvious speed
 reasons - because optimizing an Haskell application can take much time.

 Is there any document describing why there is no ghc --strict flag
 making all code strict by default?
 Wouldn't this make it easier to apply Haskell to some additional fields
 such as video processing etc?

 Wouldn't such a '--strict' flag turn Haskell/GHC into a better C/gcc
 compiler?

 Projects like this: https://github.com/thoughtpolice/strict-ghc-plugin
 show that the idea is not new.

 Eg some time ago I had to do some logfile analysis. I ended doing it in
 PHP because optimizing the Haskell code took too much time.

 Marc Weber

 ___
 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] Haskell Propaganda needed

2012-01-14 Thread Don Stewart
Hey Victor,

Thankfully, there's lots of material and experience reports available,
along with code, for the Haskell+science use case.

In my view Haskell works well as a coordination language, for
organizing computation at a high level, and thanks to its excellent
compiler and runtime, also works well for a parallel, node-level
computation. It is also fairly commonly used as a language for
generating high performance kernels thanks to EDSL support.

Thanks to the rather excellent foreign function interface, its also
trivial to interact with C (or Fortran or C++) to do number crunching,
or use other non-Haskell libraries.

Another way  to view it is the conciseness and ease of development of
Python,  with compiled, optimized code approaching C++ or C, but with
excellent parallel tools and libraries in a class of their own.

Some random links:

* The Parallel Haskell Project -
http://www.haskell.org/haskellwiki/Parallel_GHC_Project - an effort to
build parallel Haskell systems in large-scale projects, across a range
of industries. ( Six organizations participating currently,
http://www.haskell.org/haskellwiki/Parallel_GHC_Project#Participating_organisations)

* Parallel and Concurrent Programming in Haskell, a tutorial by Simon
Marlow, http://community.haskell.org/~simonmar/par-tutorial.pdf

* 11 reasons to use Haskell as a mathematician ,
http://blog.sigfpe.com/2006/01/eleven-reasons-to-use-haskell-as.html

* Math libraries on Hackage,
http://hackage.haskell.org/packages/archive/pkg-list.html#cat:math ,
including e.g. statically typed vector, cleverly optimized array
packages, and many others.

* a collection of links about parallel and concurrent Haskell,
http://stackoverflow.com/questions/3063652/whats-the-status-of-multicore-programming-in-haskell/3063668#3063668

* anything on the well-typed blog, http://www.well-typed.com/blog/


It's important to note that many of the high performance or
parallel-oriented libraries in Haskell use laziness or strictness very
carefully. Sometimes strictness is necessary for controlling e.g.
layout (see e.g. the Repa parallel arrays library:
http://www.haskell.org/haskellwiki/Numeric_Haskell%3a_A_Repa_Tutorial)
while sometimes laziness is essential (for minimizing work done in
critical sections inside locks).


Cheers,
   Don

On Sat, Jan 14, 2012 at 5:33 PM, Victor Miller victorsmil...@gmail.com wrote:
 I'm a research mathematician at a research institute with a bunch of other
 mathematicians (a number of whom are also expert programmers).  I recently
 (starting three months ago) have been learning Haskell.  I'm going to give a
 talk to the staff about it.  Most of the audience are pretty experienced
 programmers in C/C+/Python, but with little or no exposure to functional
 languages.  I'm looking for talks from which I can cannibalize good selling
 points.  I was led to Haskell by a somewhat circuitous route: at our place,
 as with most of the world, parallel programs (especially using GPUs) are
 becoming more important. A little googling lead me a few interesting
 projects on automatic mapping computations to GPUs, all of which were based
 on Haskell.   I feel that this will be the way to go.  There's one guy on
 the staff who's a demon programmer: if someone needs something to be adapted
 to GPUs they go to him.  Unfortunately I find reading his code rather
 difficult -- it's rather baroque and opaque.  Thus, I'd like something more
 high level, and something amenable to optimization algorithms.

 In my former life I worked at IBM research on one of the leading edge
 compiler optimization projects, and learned to appreciate the need for clear
 semantics in programs, not just for developing correct programs, but also to
 allow really aggressive optimizations to be performed.  This is another
 reason that I'm interested in functional languages.

 I know that I'll get peppered with questions about efficiency.  We (our
 staff) is interested in *very* large scale computations which must use the
 resources as efficiently as possible.  One of our staff members also opined
 that he felt that a lazy language like Haskell wouldn't be acceptable, since
 it was impossible (or extremely difficult) to predict the storage use of
 such a program.

 So, any suggestions are welcome.

 Victor

 ___
 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] Haskell Platform and Windows - where's 2011.4?

2011-12-27 Thread Don Stewart
All versions went live last week. Are you perhaps looking at an expired or
cached page?

On Tuesday, December 27, 2011, Bas van Dijk v.dijk@gmail.com wrote:
 On 27 December 2011 19:13, Steve Horne sh006d3...@blueyonder.co.uk
wrote:
 On haskell.org, the 2011.4.0.0 version is shown as the current stable
 release - but the most recent download link is for the 2011.2.0.0
version.

 What download link are you referring to? I see that:
 http://hackage.haskell.org/platform/windows.html correctly points to
 the 2011.4.0.0 release.

 Bas

 ___
 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] Announce: The Haskell Platform 2011.4

2011-12-17 Thread Don Stewart
We're pleased to announce the release of the Haskell Platform: a
single, standard Haskell distribution for everyone.

Download the Haskell Platform 2011.4.0.0:

http://haskell.org/platform/

The specification, along with installers (including Windows, Apple and
Unix installers for a full Haskell environment) are available.

The Haskell Platform is a single, standard Haskell distribution for
every system, in the form of a blessed library and tool suite for
Haskell distilled from the thousands of libraries on Hackage, along with
installers for a wide variety of systems. It saves developers work
picking and choosing the best Haskell libraries and tools to use for a
task.

When you install the Haskell Platform, you get the latest stable
compiler, an expanded set of core libraries, additional development
tools, and cabal-install – so you can download anything else you need
from Hackage.

What you get is specified here:

http://hackage.haskell.org/platform/contents.html

Thanks!

-- The Platform Infrastructure Team

P.S. Special thanks to Mark Lentczner for his excellent work on this release.

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


Re: [Haskell-cafe] Seeking Don Stewart

2011-07-13 Thread Don Stewart
Hi everyone,

I'm working for Standard Chartered, based in New York (currently
though, I'm in Singapore).
You can reach me on this email.

Cheers,
   Don

On Wed, Jul 13, 2011 at 5:09 PM, wren ng thornton w...@freegeek.org wrote:
 Hello all,

 Sorry for the spam. I'm trying to get ahold of Don Stewart, but it looks
 like there's some hiccup at Galois. When I mail him I get:

  d...@galois.com: host mail.galois.com[69.30.63.196] said: 550 5.1.1
      d...@galois.com... User unknown (in reply to RCPT TO command)

 Does anyone know what's up, or if there's another (non-emergency) way to
 get in touch with him?

 --
 Live well,
 ~wren



 ___
 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] Diagnose stack space overflow

2011-07-04 Thread Don Stewart
Profile!!

E.g.

http://stackoverflow.com/questions/6429085/haskell-heap-issues-with-parameter-passing-style/6429888#6429888



On Mon, Jul 4, 2011 at 11:44 AM, Logo Logo sarasl...@gmail.com wrote:
 Hi,

 For the following error:

 Stack space overflow: current size 8388608 bytes.
 Use `+RTS -Ksize -RTS' to increase it.

 I want to find out the culprit function and rewrite it tail-recursively. Is
 there a way to find out which function is causing this error other
 than reviewing the code manually?

 Thanks,
 Loganathan
 ___
 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] NVIDIA's CUDA and Haskell

2011-07-04 Thread Don Stewart
There's a lot of active work:

Direct access to CUDA: http://hackage.haskell.org/package/cuda
CUDA in Haskell: http://hackage.haskell.org/package/language-c-quote
Direct access to OpenCL: http://hackage.haskell.org/package/OpenCLRaw
High-level pure data parallelism targetting your GPU:
http://hackage.haskell.org/package/accelerate

On Mon, Jul 4, 2011 at 8:09 PM, Vasili I. Galchin vigalc...@gmail.com wrote:
 Hi,

   NVIDIA's CUDA library seems to be really hot in the massively parallel
 world: http://www.nvidia.com/object/cuda_home_new.html. I realize that given
 CUDA seems to be implemented in an extension of ANSI C that it is pervaded
 by statefulness. However, is there any effort to build a bridge between
 Haskell and CUDA, foreign language bindings or maybe better yet a monad to
 encapsulate state??

 Kind regards,

 Vasili

 ___
 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] Lambdabot plugin system description

2011-07-01 Thread Don Stewart
In fact  there is!

Plugging Haskell In. André Pang, Don Stewart, Sean Seefried, and
Manuel M. T. Chakravarty. In Proceedings of the ACM SIGPLAN Workshop
on Haskell, pages 10-21. ACM Press, 2004

http://www.cse.unsw.edu.au/~dons/papers/hs-plugins.pdf

And

Dynamic Applications From the Ground Up. Don Stewart and Manuel M. T.
Chakravarty. In Proceedings of the ACM SIGPLAN Workshop on Haskell,
pages 27-38. ACM Press, 2005

http://www.cse.unsw.edu.au/~dons/papers/yi.pdf

--   Don

On Fri, Jul 1, 2011 at 7:43 PM, Richard Wallace
rwall...@thewallacepack.net wrote:
 Hey all,

 I'm curious if there are any papers or anything else describing the
 plugin system in Lambdabot.  If not I'll dig through the code, but my
 Haskell isn't yet that strong so a higher level introduction would be
 very helpful.

 Thanks,
 Rich

 ___
 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] View Thunk Evaluation

2011-06-26 Thread Don Stewart
Yes, via the -hpc tracing mechanism.

When executed HPC generates a highlighted log of your source, and
expressions that aren't evaluated will be marked up in a special
color.

On Sun, Jun 26, 2011 at 9:22 PM, Tom Murphy amin...@gmail.com wrote:
 Hi All,
     Is there a way to determine whether a thunk was evaluated during
 code's execution?

 Thanks,
 Tom

 ___
 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] Haskell on iPad? (Scheme and Ocaml are there)

2011-06-18 Thread Don Stewart
See e.g.

http://www.haskell.org/haskellwiki/IPhone

http://www.haskell.org/haskellwiki/IPhone
https://github.com/dpp/LispHaskellIPad

https://github.com/dpp/LispHaskellIPad

On Sat, Jun 18, 2011 at 12:18 PM, John Velman vel...@cox.net wrote:


 There are (at least) two Scheme interpreters for iPad at the iTunes store:
 PixieScheme and GambitREPL.  Both allow entry of scripts, by typing or
 pasting.  The Gambit community is very busy trying to expand the usefulness
 of their interpreter.  Both have pretty good interfaces.

 There is also an Ocaml app, but I don't know or want to know Ocaml, and the
 interface looks very unfriendly.

 I'd really like to have something like this in Haskell, in the education
 pot, as is the GambitREPL.  Hugs is written in C, if I recall correctly.
 Would it be possible to compile Hugs for the iPad processor, taking out
 enough system calls to make it acceptable?

 John Velman

 ___
 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] Haskell *interpreter* on iPad? (Scheme and Ocaml are there)

2011-06-18 Thread Don Stewart
See also the cloud: http://tryhaskell.org

:-)

On Sat, Jun 18, 2011 at 1:46 PM, John Velman vel...@cox.net wrote:

 Well, I'm not interested in a lisp interpreter written in Haskell.  Nor am
 I (at the moment) interested in writing an iPad app in Haskell.

 I changed the subject to clarify.

 What I would like to see is A Haskell Interpreter on the iPad.

 To further emphasize, I'd like to type in (or paste in) Haskell code and
 have it executed on the iPad.  To reiterate:  Something like Hugs, or ghci
 on the iPad.

 By the way, there are three Scheme interpreters in the iPad app store.  In
 addition to the two I previously mentioned, there is iScheme.

 - John Velman



 On Sat, Jun 18, 2011 at 12:43:45PM -0400, Don Stewart wrote:
  See e.g.
 
  http://www.haskell.org/haskellwiki/IPhone
 
  http://www.haskell.org/haskellwiki/IPhone
  https://github.com/dpp/LispHaskellIPad
 
  https://github.com/dpp/LispHaskellIPad
 
  On Sat, Jun 18, 2011 at 12:18 PM, John Velman vel...@cox.net wrote:
 
  
   There are (at least) two Scheme interpreters for iPad at the iTunes
 store:
   PixieScheme and GambitREPL.  Both allow entry of scripts, by typing or
   pasting.  The Gambit community is very busy trying to expand the
 usefulness
   of their interpreter.  Both have pretty good interfaces.
  
   There is also an Ocaml app, but I don't know or want to know Ocaml, and
 the
   interface looks very unfriendly.
  
   I'd really like to have something like this in Haskell, in the
 education
   pot, as is the GambitREPL.  Hugs is written in C, if I recall
 correctly.
   Would it be possible to compile Hugs for the iPad processor, taking out
   enough system calls to make it acceptable?
  
   John Velman
  
   ___
   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] Haskell *interpreter* on iPad? (Scheme and Ocaml are there)

2011-06-18 Thread Don Stewart
Oh, Scheme is trivial to implement, when compared with Haskell. So
people write it from scratch as a tutorial exercise.

Haskell isn't trivial to implement from scratch, so instead we port
existing implementations mostly.

That means really, porting Hugs or GHC. And you've been pointed at examples.

I think people are clearly keen for this, now it is a small matter of
programming talent and will.

-- Don

On Sat, Jun 18, 2011 at 3:03 PM, John Velman vel...@cox.net wrote:
 On Sat, Jun 18, 2011 at 10:44:01PM +0400, MigMit wrote:

 Well, this is my point.  THERE ARE 3 SCHEME INTERPRETERS in the iPad app
 store.

 They run on factory iPads, not jailbroken.

 The GUI for the gambitREPL  (Read, Evaluate, Print, Loop) is just like a
 console.   Input a scheme expression.  CR. Answer appears, new prompt.

 In haskell we need to allow for some way to input layout.  I don't recall
 how Hugs handles this, if at all.

 There are probably 5 or 10 people out there who want to learn functional
 programming, and they are studying Scheme on their iPads.  Or Ocaml.

 I don't forsee doing production programming ON THE IPAD, but experimenting,
 testing some functions, and, by the way, learning Haskell.

 While I'm fantasizing, something like Hugs or ghci with SOE would really be
 neat.

 Sorry for shouting  :-)

 John Velman

 Well, Haskell is fun, isn't it? And that's what iPhone is perfect for: fun.

 Back when I had iPod Touch 1G (jailbroken, of course), I used to run Hugs on 
 it. Now I would love to see a Haskell interpreter in the App Store -- which, 
 by the way, is possible; as there are Scheme interpreters there, why not 
 Haskell?

 Отправлено с iPhone

 Jun 18, 2011, в 22:27, Jack Henahan jhena...@uvm.edu написал(а):

  I suppose you could make a GUI, by why? Given that you'll have to be 
  working on a jailbroken device, anyway, one could just as well use one of 
  the numerous terminal emulators now floating around for jailbroken iOS. 
  That said, the idea of people writing Haskell on phones and iPads and so 
  on makes me just a little bit grinny.
 
  On Jun 18, 2011, at 2:17 PM, Alexander Solla wrote:
 
 
 
  On Sat, Jun 18, 2011 at 10:46 AM, John Velman vel...@cox.net wrote:
  To further emphasize, I'd like to type in (or paste in) Haskell code and
  have it executed on the iPad.  To reiterate:  Something like Hugs, or ghci
  on the iPad.
 
  Since the iPhone OS is pretty much OS X for ARM, and GHC apparently now 
  supports cross-compilation, you can compile GHC for iOS.  I guess you 
  could cross compile Hugs with GCC.  Doing so probably isn't trivial, but 
  it should be straightforward.
 
  I bet you could even use Xcode to make a graphical user interface to GHCi.
  ___
  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


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


Re: [Haskell-cafe] Toy implementation of the STG machine

2011-06-11 Thread Don Stewart
See also:

 * STG machine in Coq,
http://www.cs.ox.ac.uk/files/3858/pirog-biernacki-hs10.pdf

http://www.cs.ox.ac.uk/files/3858/pirog-biernacki-hs10.pdfAlso

 * ] Jon Mountjoy. The spineless tagless G-machine, naturally. 1998 ACM
SIGPLAN International Conference on Functional Programming,
SIGPLAN Notices, Vol. 34, No. 1, pages 163–173, Baltimore,
Maryland, September 1998. ACM Press.

On Sat, Jun 11, 2011 at 4:32 PM, Thomas Schilling
nomin...@googlemail.comwrote:

 Does Bernie Pope's http://www.haskell.org/haskellwiki/Ministg work for
 you?

 On 11 June 2011 21:19, Florian Weimer f...@deneb.enyo.de wrote:
  I'm looking for a simple implementation of the STG machine to do some
  experiments, preferably implemented in something with memory safety.
  Performance is totally secondary.  I'm also not interested in garbage
  collection details, but I do want to look at the contents of the
  various stacks.
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 



 --
 Push the envelope. Watch it bend.

 ___
 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] haskell platform question

2011-06-07 Thread Don Stewart
It should build. If it doesn't, please report a bug.

On Tue, Jun 7, 2011 at 8:53 AM, Tim Docker t...@dockerz.net wrote:
 I'd like to build the haskell platform against a recent GHC snapshot, for
 testing purposes.

 I see that I can download the source for the platform from:


 http://lambda.galois.com/hp-tmp/2011.2.0.1/haskell-platform-2011.2.0.1.tar.gz

 with instructions:

    http://www.vex.net/~trebla/haskell/haskell-platform.xhtml

 However when I tried this some months ago, I found that some of the packages
 in the above source fail to build due to recent ghc changes (eg it's
 stricter handling of bang patterns).

 Is there a more recent beta snapshot of the platform? Or a darcs/git repo
 somewhere? I imagine wanting to build the platform against bleeding edge ghc
 would be a pretty common desire.

 Tim

 ___
 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] haskell platform question

2011-06-07 Thread Don Stewart
Oh, sorry, missed the first line. Building against GHC snapshots isn't
supported.

On Tue, Jun 7, 2011 at 6:48 AM, Don Stewart don...@gmail.com wrote:
 It should build. If it doesn't, please report a bug.

 On Tue, Jun 7, 2011 at 8:53 AM, Tim Docker t...@dockerz.net wrote:
 I'd like to build the haskell platform against a recent GHC snapshot, for
 testing purposes.

 I see that I can download the source for the platform from:


 http://lambda.galois.com/hp-tmp/2011.2.0.1/haskell-platform-2011.2.0.1.tar.gz

 with instructions:

    http://www.vex.net/~trebla/haskell/haskell-platform.xhtml

 However when I tried this some months ago, I found that some of the packages
 in the above source fail to build due to recent ghc changes (eg it's
 stricter handling of bang patterns).

 Is there a more recent beta snapshot of the platform? Or a darcs/git repo
 somewhere? I imagine wanting to build the platform against bleeding edge ghc
 would be a pretty common desire.

 Tim

 ___
 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] OK! I have a Mac with Snow Leopard 10.6.7?, Xcode 3.2.6, Haskell Platform 2011.2.0.1; What are 2or 3 ways so far to get a GUI graphics?

2011-06-05 Thread Don Stewart
Answers cached on stackoverlow:

http://stackoverflow.com/questions/5612201/haskell-library-for-2d-drawing/5613788#5613788

for 2D graphics.

http://stackoverflow.com/questions/2860988/haskell-ui-framework

for UIs.

Cheers,
   Don

On Sun, Jun 5, 2011 at 8:18 PM, KC kc1...@gmail.com wrote:
 --
 --
 Regards,
 KC

 ___
 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] *GROUP HUG*

2011-06-01 Thread Don Stewart
http://stackoverflow.com/questions/6172004/writing-foldl-using-foldr/6172270#6172270

Thank Graham Hutton and Richard Bird.

On Wed, Jun 1, 2011 at 7:12 PM, Tom Murphy amin...@gmail.com wrote:

 How about this:

 myFoldr :: (a - b - b) - b - [a] - b
 myFoldr f z xs = foldl' (\s x v - s (x `f` v)) id xs $ z

 Cheers,
 Ivan



 Great! Now I really can say Come on! It's fun! I can write foldr with foldl!

 ___
 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] Efficient object identity (aka symbols as data)

2011-05-29 Thread Don Stewart
 Why doesn't Haskell have built in syntactic sugar for atoms?
 -- Anupam

I think because of deriving Enum.

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


Re: [Haskell-cafe] ANNOUNCE: HaNS-2.1.0.0

2011-05-24 Thread Don Stewart
Yay! The Hackage URL is:

http://hackage.haskell.org/package/hans

Cheers,
   Don

On Tue, May 24, 2011 at 11:39 AM, Trevor Elliott tre...@galois.com wrote:
 Galois, Inc. is pleased to announce the release of HaNS, the Haskell
 Network Stack.  HaNS is a lightweight, pure Haskell network stack that
 can be used for Haskell networking in the context of the HaLVM, or with
 a Linux tap device. Currently, HaNS supports 802.3, IPv4, ARP, DHCP
 (partially), ICMP, UDP, and TCP.

    On Hackage: http://hackage.haskell.org/package/HaNS
    Git repo:   http://code.galois.com/cgi-bin/gitweb

 The TCP component is a port of Peng Li and Stephan Zdancewic's Haskell
 TCP library, which in turn was translated from Norrish et al's HOL4 TCP
 specification.

 What might you use HaNS for? Developing new and interesting networking
 protocols, at any layer of the network stack, or your own variants of
 existing protocols. HaNS allows HaLVM nodes to support networking,
 meaning you can run experimental network services directly on top of the
 HaLVM (without any pesky OS getting in the way). There are probably lots
 of other cool applications of HaNS we haven't though of yet.

 HaNS is released under a BSD license, and should be considered
 experimental at this stage.

 If you have any questions please contact the HaLVM team at

    halvm-de...@community.galois.com.

 -- Trevor Elliott (for the HaLVM team)

 P.S. If you're building with the HaLVM, make sure to add -fhalvm to your
 cabal install invocation.


 = References =

 HaLVM:          http://halvm.org
 Haskell TCP:    http://hackage.haskell.org/package/tcp


 ___
 Libraries mailing list
 librar...@haskell.org
 http://www.haskell.org/mailman/listinfo/libraries



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


Re: [Haskell-cafe] The Lisp Curse

2011-05-19 Thread Don Stewart
This is classic community trolling behavior, Andrew.

You post something inflammatory, questioning the core value of our
project, without a clear argument about why it article relevant, and
then step away to let a monster thread consume everything, as people
try to work out what your point was, not trying to argue a point, or
other wise participate.

Doing this, year after year, is bad for -cafe@ and bad for the
community, and why I don't use -cafe@ for problem solving anymore.

-- Don

I'm glad my mail reader has a mute button.

On Thu, May 19, 2011 at 12:39 PM, Stephen Tetley
stephen.tet...@gmail.com wrote:
 Och Mr Coppin

 Lisp is a fine language, but all Lisp essays you'll find on the
 internet except Richard Gabriel's Worse is Better are absolute tosh.

 Read Olin Shiver's introduction to SRE regex notation for an
 intelligent contribution to the 6 different libraries problem you
 seem to be having, rather than some cargo cultist muddy thinking.

 http://www.scsh.net/docu/post/sre.html

 By the way, referencing the original article circa half way down -
 didn't Mark P. Jones write Gofer and the original Hugs by himself  -
 people actually used those rather than Qi.

 ___
 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] Is fusion overrated?

2011-05-18 Thread Don Stewart
Also, we do fusion on strict structures (e.g. vectors), where you get
back O(n) on each fused point. Obviously, it is less of a win on lazy
structures than the (pathological) case of strict data, but it is
still a win.

-- Don

On Tue, May 17, 2011 at 11:07 PM, Ben Lippmeier b...@ouroborus.net wrote:

 On 18/05/2011, at 15:55 , Roman Cheplyaka wrote:
 Of course I don't claim that fusion is useless -- just trying to
 understand the problem it solves. Are we saving a few closures and cons
 cells here?

 And thunk allocations, and thunk entries. Entering a thunk costs upwards of 
 20 cycles, while performing a single addition should only cost one. Imagine 
 every thunk entry is a function call. You don't want to call a whole function 
 just to add two numbers together.

 Those few closures and cons cells can be surprisingly expensive when 
 compared to native ALU instructions on a modern machine.

 Ben.





 ___
 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] fishing for ST mutable Vector examples

2011-05-17 Thread Don Stewart
Yes, the differences between

 * vector
 * array
 * repa

were discussed this week on Stack Overflow:

 
http://stackoverflow.com/questions/6006304/what-haskell-representation-is-recommended-for-2d-unboxed-pixel-arrays-with-mill

The reason to prefer vectors of arrays are:

 * flexible interface
 * generic interface
 * growable
 * fusible operations.

They do not support multi-dimension indexing though. For that, there
is repa, which has a rich interface, supports fusion and slicing, and
is automagically parallel.   However, repa arrays are not mutable. So
if you need multidimensional mutable arrays, either the regular array
package, or hmatrix.

On Tue, May 17, 2011 at 4:15 PM, Yves Parès limestr...@gmail.com wrote:
 Hello all,

 By the way, is there any reason to prefer package 'vector' over package
 'array'? Do they just provide different interfaces to similar
 functionnalities or are there real performance stakes?
 I personnaly prefer Data.Array, since:
 - It gives the possibility to index with something else than integers
 (thanks to Ix class)
 - It provides Foldable/Traversable instances (better abstraction, so)


 2011/4/22 Daniel Fischer daniel.is.fisc...@googlemail.com

 On Friday 22 April 2011 20:14:38, Stephen Tetley wrote:
  Hi Brad
 
  I think all you can do with an ST array is covered by the MArray class
  and its derived operations - note the class is exported opaquely from
  Data.Array.MArray - it has these two members that aren't exported so
  aren't documented:
 
 
  unsafeRead  :: Ix i = a i e - Int - m e
  unsafeWrite :: Ix i = a i e - Int - e - m ()

 Those are available from Data.Array.Base. I use them a lot, because
 there's
 no point in letting the runtime check array bounds after I just did to
 determine whether the loop is finished.

 
  To actually read and write you have to use the safe derived operations
  which wrap the unsafe versions:
 
  readArray :: (MArray a e m, Ix i) = a i e - i - m e
  writeArray :: (MArray a e m, Ix i) = a i e - i - e - m ()
 
  For practical purposes I've found STArray's a bit of a white elephant

 I on the other hand use 'STUArray's very much. When you fill an array with
 an algorithm which works best with mutation (a sieve for example) and
 afterwards use it only for querying, runSTUArray (or runSTArray) is a
 great
 friend. ST guarantees that no other thread can mess with your array while
 you build it, when you're done it's immutable. IO doesn't give you these
 guarantees, you have to ascertain yourself that no other thread can mutate
 your array.

 It's the same for 'Vector's, ST's phantom type parameter isolates you from
 the outside world, with IOVectors, you have to do the protection yourself.
 I think vector doesn't provide an analogue to runST(U)Array, but if you
 need it, you can write

 runST (do
   vec - stuff
   frz - unsafeFreeze vec
   return frz

 yourself.

  - I always use IOArray instead, as I've either needed to initially
  read an array from file or write one to file at the end.

 On the other hand, if you're doing IO, an IOArray is a fairly natural
 choice.

 ___
 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] fishing for ST mutable Vector examples

2011-05-17 Thread Don Stewart
Well, repa doesn't have a GPU backend. So if you need GPU stuff, you
probably do need to look at accelerate.
I think Repa is in beta now, the API might change a little (e.g.
we're discussing making the stuff under the hood Storable class
friendly). It also only has a small number of users, while vector has
thousands.

So, it depends on how much you like new code. There are probably still
bugs in Repa, and API changes ahead, however, it is more stable than
accelerate, which is a whole different beast. If you need
multi-dimensional, *mutable* arrays, hmatrix or the array package are
very stable, just not as much fun.

-- Don

On Tue, May 17, 2011 at 5:31 PM, Felipe Almeida Lessa
felipe.le...@gmail.com wrote:
 On Tue, May 17, 2011 at 8:30 PM, Don Stewart don...@gmail.com wrote:
  * vector
  * array
  * repa

 Don, do you think that repa is as recommended as vector for
 production applications?  I'm asking so because it is my understanding
 that accelerate still isn't mature enough to be used in production
 code, but I'm told vector is =).

 Cheers, =D

 --
 Felipe.


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


Re: [Haskell-cafe] No fish, please

2011-05-17 Thread Don Stewart
I'm intrigued by  the idea of Hackage docs that don't use Haddock.

IF you do have better docs, host them somewhere, and put a link
prominently in the .cabal file synopsis.

On Tue, May 17, 2011 at 9:25 PM, John Millikin jmilli...@gmail.com wrote:
 Is there any way to indicate to Hackage that it should not try to generate
 Haddock documentation? I'm concerned for two use cases for packages using a
 different docs system:

 1) A user might see the commentless auto-generated haddock and believe the
 package is undocumented.
 2) A user might find the haddock through Google, and not realize there's
 real documentation available elsewhere.

 Purposfully causing Hackage's haddock step to fail will mark the package as
 a build failure, which gives a bad impression to potential users.

 ___
 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] Accelerate package (CUDA). How to actually create an array?

2011-05-16 Thread Don Stewart
You might want to read the Repa tutorial:

http://www.haskell.org/haskellwiki/Numeric_Haskell:_A_Repa_Tutorial

e.g.

fromList (Z :. (3::Int)) [1,2,3]

2011/5/16 Grigory Sarnitskiy sargrig...@ya.ru:
 There's fromIArray and fromList [1].  Does that answer your question?

 Huh, yes, thank you! But still I don't get it. Neither

 arr1 = fromList 3 [1,2,3] :: Array DIM1 Int

 nor

 arr1 = fromList (1,3) [1,2,3] :: Array DIM1 Int

 works

 ___
 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] No fish, please

2011-05-12 Thread Don Stewart
No, you should be using Haddock.

If you wish to generate docs some other way, you are free to host that
on your own site, and link to it from the Hackage page.

On Thu, May 12, 2011 at 10:45 AM, Andrew Coppin
andrewcop...@btinternet.com wrote:
 Both Hackage and Cabal seem to assume as a matter of course that I want to
 use Haddock to generate all my documentation. Suppose I decide to violate
 this assumption. Then what?

 1. Is there some way I can include my own HTML documentation in the package
 tarball and have Hackage/Cabal use it?

 2. Is there a way to tell Hackage/Cabal to use some tool besides Haddock?

 ___
 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] Proposal to incorporate Haskell.org

2011-05-11 Thread Don Stewart
The intent is that all management of haskell.org infrastructure
continues to be done by the haskell.org committee, following this
charter (e.g. the team that has been making decisions about
haskell.org servers and systems for the past 6 months):

http://www.haskell.org/haskellwiki/Haskell.org_committee

So the day-to-day work of haskell.org that we all see remains with the
community. The paper filing and legal work is done by the SFC support.



The process for the haskell.org committee itself was voted on last year:

 *  The committee consists of 7 members. Members are expected to serve
a 3 year term, and terms are staggered so that 2 or 3 members step
down each year, at the end of October.

 *  The members will elect one of their number to be chair each year.
The chair is responsible for making sure that things keep moving, and
to ensure that a conclusion is reached on any issues raised.

 *When a member steps down, either because they have reached the
end of their term or because other circumstances require them to step
down early, open self-nominations will be sought from the community
via the haskell@ mailing list. Previous committee members, including
those who have just stepped down, will also be eligible for
nomination. The committee will then select a replacement from amongst
those nominated.

 *   Each year, the committee will post a statement of the haskell.org
assets, and the transactions for that year. Some details may be
omitted, e.g. for confidentiality of donors.

Cheers,
   Don

On Wed, May 11, 2011 at 2:16 AM, Simon Peyton-Jones
simo...@microsoft.com wrote:
 Dear haskell.org committee

 Great stuff.  Thanks for getting this together.

 Things I wondered about are:
        - who will run the haskell.org entity?
        - how are they chosen?  do they have fixed terms?
        - how are they accountable to the Haskell Community
          (eg an a brief annual report would be good;
             since money is involved, accounts perhaps)

 None of these look like being problems to me, but I think we should have a 
 page that sets out these matters -- a kind of constitution for haskell.org, 
 if you like -- as part of the process.

 Simon

 | -Original Message-
 | From: libraries-boun...@haskell.org [mailto:libraries-boun...@haskell.org] 
 On Behalf
 | Of Don Stewart
 | Sent: 10 May 2011 23:45
 | To: hask...@haskell.org; Haskell Libraries; GHC Users Mailing List; 
 haskell-cafe;
 | commit...@haskell.org
 | Subject: Proposal to incorporate Haskell.org
 |
 | Hello everyone.
 |
 | The haskell.org committee[1], in the interest of the long-term stability
 | of the open source Haskell community infrastructure, has decided to
 | incorporate haskell.org as a legal entity. This email outlines our
 | recommendation, and seeks input from the community on this decision.
 |
 | The committee's proposal is that haskell.org incorporate as an entity
 | under the Software Freedom Conservancy umbrella organization (the same group
 | that Darcs joined recently):
 |
 |     http://sfconservancy.org/
 |
 | If we proceed with this move, haskell.org will be a legal entity, and
 | registered as a non-profit, allowing us to more directly accept
 | (US tax-deductible) donations, and to invest in assets that benefit the
 | Haskell open source community.
 |
 | We welcome your feedback on the proposal attached below.
 |
 | -- Don Stewart (on behalf of the Haskell.org committee)
 |
 |
 |
 | 
 |
 | = A proposal for the incorporation of Haskell.org =
 |
 | In recent years, haskell.org has started to receive assets, e.g. money from
 | Google Summer Of Code, donations for Hackathons, and a Sparc machine for 
 use in
 | GHC development. We have also started spending this money: in particular, on
 | hosting haskell.org itself. There is also interest in running fundraising
 | drives for specific things such as Hackathon sponsorship and hosting fees.
 |
 | However, haskell.org doesn't currently exist as a legal entity, meaning that
 | these assets have had to be held on our behalf by other entities, such as
 | Galois and various universities. This leads to tricky situations, with 
 no-one
 | being sure who should decide how the haskell.org assets can be used.
 |
 | To solve these problems, we propose that haskell.org applies to become a 
 member
 | project of the Software Freedom Conservancy (SFC)
 | http://conservancy.softwarefreedom.org/. The SFC is a non-profit 
 organization
 | that provides free financial and administrative services to open source
 | projects. Additionally, it has 501(c)(3) status, meaning donations from the 
 US
 | are tax-deductible. The SFC would hold haskell.org's money and other assets,
 | and would be able to accept donations on behalf of haskell.org.
 |
 | The haskell.org committee, as described here [2], will make decisions

[Haskell-cafe] Proposal to incorporate Haskell.org

2011-05-10 Thread Don Stewart
Hello everyone.

The haskell.org committee[1], in the interest of the long-term stability
of the open source Haskell community infrastructure, has decided to
incorporate haskell.org as a legal entity. This email outlines our
recommendation, and seeks input from the community on this decision.

The committee's proposal is that haskell.org incorporate as an entity
under the Software Freedom Conservancy umbrella organization (the same group
that Darcs joined recently):

http://sfconservancy.org/

If we proceed with this move, haskell.org will be a legal entity, and
registered as a non-profit, allowing us to more directly accept
(US tax-deductible) donations, and to invest in assets that benefit the
Haskell open source community.

We welcome your feedback on the proposal attached below.

-- Don Stewart (on behalf of the Haskell.org committee)





= A proposal for the incorporation of Haskell.org =

In recent years, haskell.org has started to receive assets, e.g. money from
Google Summer Of Code, donations for Hackathons, and a Sparc machine for use in
GHC development. We have also started spending this money: in particular, on
hosting haskell.org itself. There is also interest in running fundraising
drives for specific things such as Hackathon sponsorship and hosting fees.

However, haskell.org doesn't currently exist as a legal entity, meaning that
these assets have had to be held on our behalf by other entities, such as
Galois and various universities. This leads to tricky situations, with no-one
being sure who should decide how the haskell.org assets can be used.

To solve these problems, we propose that haskell.org applies to become a member
project of the Software Freedom Conservancy (SFC)
http://conservancy.softwarefreedom.org/. The SFC is a non-profit organization
that provides free financial and administrative services to open source
projects. Additionally, it has 501(c)(3) status, meaning donations from the US
are tax-deductible. The SFC would hold haskell.org's money and other assets,
and would be able to accept donations on behalf of haskell.org.

The haskell.org committee, as described here [2], will make decisions on
spending assets and other decisions related to governing the non-profit.


Before proceeding, we are inviting input from the community in the form
of specific objections or queries regarding the plan.

We've tried to answer some of the most likely questions:

Q: Does this mean that my Haskell project must now be covered by a
 copyleft licence such as GPL?
A: No, but Haskell projects using haskell.org resource should use an
Open Source licence
 http://www.opensource.org/licenses/alphabetical.

Q: Will it still be possible to use community.h.o to host
 non-open-source material, such as academic papers?
A: An overall minority of such content, as is the current situation, is
not a problem.

Q: Will it still be possible to have job ads on the haskell.org mailing
lists and website?
A: Yes.

Q: Will this affect our ability to host the Haskell Symposium
http://www.haskell.org/haskell-symposium/  and Industrial Haskell
Grouphttp://industry.haskell.org/  webpages within haskell.org?
A: No.

Q: What will be the relationship between haskell.org and other
organizations such as the Haskell Symposium and Industrial Haskell
Group?
A: Those organisations will continue to exist as separate entities.

Q: If an umbrella non-profit organisation The Haskell Foundation was
created, would haskell.org be able to join it?
A: Yes. It's likely that in such a scenario, the Haskell Foundation
would become the owner of the haskell.org domain name, with the cost
divided between the members. The entity that is part of the SFC would
be renamed community.haskell.org in order to avoid confusion.

[1]: http://www.haskell.org/haskellwiki/Haskell.org_committee
[2]: http://www.haskell.org/haskellwiki/Haskell.org_committee#Operation

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


Re: [Haskell-cafe] Please add instance Semigroup Text

2011-05-03 Thread Don Stewart
Getting stuff into the HP is a different problem, and something I'm
working on addressing in coming weeks... stay tuned.

On Tue, May 3, 2011 at 2:33 PM, Bryan O'Sullivan b...@serpentine.com wrote:
 On Tue, May 3, 2011 at 1:14 PM, Yitzchak Gale g...@sefer.org wrote:

 You are quite right. These should really be defined in their
 respective packages. I don't think it's too onerous for them
 to add a dependency on semigroups, even before you
 reverse the few lightweight dependencies that semigroups has.

 Unfortunately, the semigroups package will have to go into the Platform
 before either text or bytestring can make use of it. I think that would be
 great to have, but the getting from here to there is not necessarily fun.
 ___
 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] Advertisement: the Haskell Stack Overflow Q A site

2011-05-03 Thread Don Stewart
Hey all,

I thought I'd just make a quick advertisement for  the Haskell Stack
Overflow community:

 http://stackoverflow.com/questions/tagged/haskell

as a forum for questions and answers on beginner to advanced Haskell problems.

The site is very active, with roughly as many questions being asked on
SO as on haskell-cafe these days.

One of the benefits of a site like SO as a forum is the ability to
record and link to prior work, edit for technical errors, and easily
search and categorize past answers. It is also less prone to noise,
for those suffering from cafe overload.

Cheers,
   Don

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


Re: [Haskell-cafe] How to make ghc 7 with llvm?

2011-04-28 Thread Don Stewart
Use the -fllvm flag.

On Thu, Apr 28, 2011 at 6:49 PM, Magicloud Magiclouds
magicloud.magiclo...@gmail.com wrote:
 Hi,
  As I recalled, ghc started to support llvm from version 7.
  But there is a problem: there is no option to make ghc with llvm. So
 Library within ghc source will be in gcc's binary format. Then when I
 install other packages, they may complain that the binary format is
 not llvm, so they install some libraries again.
  Any way I could make ghc 7 with llvm?
 --
 竹密岂妨流水过
 山高哪阻野云飞

 ___
 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] Is Hugs dead?

2011-04-22 Thread Don Stewart
Strong recommendation is to use the Haskell Platform and GHC as your
development base, unless you have very specific reasons to use Hugs or
one of the other compilers.

-- Don

On Fri, Apr 22, 2011 at 5:16 AM, Robert Clausecker fuz...@gmail.com wrote:
 Some weeks ago, I mirrored the hugs repo to github.
 (https://github.com/fuzxxl/Hugs) This was, when I found out, that the
 last commit was about 2 years ago. Also, since some of the dependencies
 moved, I was unable to build hugs.

 Now my question is: Is Hugs dead? What's the status of development of
 hugs?

 Yours, Robert Clausecker



 ___
 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] fishing for ST mutable Vector examples

2011-04-22 Thread Don Stewart
In my tutorial on using vectors,

http://www.haskell.org/haskellwiki/Numeric_Haskell:_A_Vector_Tutorial

There's some examples:

http://www.haskell.org/haskellwiki/Numeric_Haskell:_A_Vector_Tutorial#Impure_Arrays

that work in IO, and should work equally well in ST (as vectors are
parameterized by either primitive monad).

On Fri, Apr 22, 2011 at 10:32 AM, brad clawsie claw...@fastmail.fm wrote:
 hi all

 i was wondering if anyone could post some minimal examples on using
 mutable Vectors in the ST monad. i've been digging around in the usual
 places but haven't been able to find anything to get me over the hump

 thanks in advance
 brad

 ___
 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] Painless parallelization.

2011-04-19 Thread Don Stewart
 to write a pure functional parallel code with the level of abstraction I used 
 in Haskell?

The status of parallel programming in Haskell is loosely maintained here:


http://stackoverflow.com/questions/3063652/whats-the-status-of-multicore-programming-in-haskell/3063668#3063668

Your options, as of today,

 * The par-monad package and a monad for deterministic parallelism,
Simon Marlow -- more control over pure parallelism than
strategies/par/pseq.

 * The parallel package

 * Repa (parallel arrays)

 * DPH (for more experimenetal use)

 * Explict thread-based shared memory concurrency and multicore
parallelism (forkIO/MVars/STM)

On Tue, Apr 19, 2011 at 11:51 AM, Grigory Sarnitskiy sargrig...@ya.ru wrote:
 Hello, I'm searching a way to benefit from modern hardware in my programs.

 I consider parallel programing to be actually easier than sequential one. 
 Parallel computation allows to avoid sophisticated algorithms that were 
 developed to gain performance on sequential architecture. It should also 
 allow to stop bothering about using immutable objects --- immutable parallel 
 arrays should be as fast as mutable ones, right? (provided there is enough 
 cores)

 So what are the options to write a pure functional parallel code with the 
 level of abstraction I used in Haskell? So far I've found Data Parallel 
 Haskell for multicore CPU's and Data.Array.Accelerate for GPU's. It would be 
 nice to have something at the release state, rather than some beta.

 ___
 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] [Haskell] select(2) or poll(2)-like function?

2011-04-18 Thread Don Stewart
Redirecting to haskell-cafe@, where this kind of long discussion belongs.

On Mon, Apr 18, 2011 at 9:07 AM, Colin Adams
colinpaulad...@googlemail.com wrote:


 On 18 April 2011 16:54, Ertugrul Soeylemez e...@ertes.de wrote:

 
  Well, *someone* has to worry about robustness and scalability. Users
  notice when their two minute system builds start taking four minutes
  (and will be at my door wanting me to fix it) because something didn't
  scale fast enough, or have to be run more than once because a failing
  component build wasn't restarted properly. I'm willing to believe that
  haskell lets you write more scalable code than C, but C's tools for
  handling concurrency suck, so that should be true in any language
  where someone actually thought about dealing with concurrency beyond
  locks and protected methods. The problem is, the only language I've
  found where that's true that *also* has reasonable tools to deal with
  scaling beyond a single system is Eiffel (which apparently abstracts
  things even further than haskell - details like how concurrency is
  achieved or how many concurrent operations you can have are configured
  when you start an application, *not* when writing it). Unfortunately,
  Eiffel has other problems that make it undesirable.

 I can't make a comparison, because I don't know Eiffel.

 I do, and I don't recognize what the OP is referring to - I suspect he meant
 Erlang.

 --
 Colin Adams
 Preston, Lancashire, ENGLAND
 ()  ascii ribbon campaign - against html e-mail
 /\  www.asciiribbon.org   - against proprietary attachments

 ___
 Haskell mailing list
 hask...@haskell.org
 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] Haskell Platform 2011.2.0.1 now available

2011-04-16 Thread Don Stewart
On Fri, Apr 15, 2011 at 11:50 PM, Joachim Breitner nome...@debian.org wrote:
 Hi,

 Am Freitag, den 15.04.2011, 15:44 -0700 schrieb Don Stewart:
 We're pleased to announce the 2011.2.0.1 release of the Haskell Platform:
 a single, standard Haskell distribution for everyone.

 Download the Haskell Platform 2011.2.0.1:

     http://haskell.org/platform/

 or use Debian unstable, which ships this version of the platform since
 five days already: http://people.debian.org/~nomeata/platform.html


Good work!

Is the link to Debian on the http://haskell.org/platform homepage correct?


  * We only ship it already because the file on
 http://code.galois.com/darcs/haskell-platform/haskell-platform.cabal
 has already changed earlier, which was linked by
 http://hackage.haskell.org/platform/changelog.html so we thought this is
 already official and released and we just missed the announcement.

Do you watch the haskell-platf...@projects.haskell.org mailing list?
There we announced the freeze, and the initial release candidates.


 Maybe it would be better if released versions get their own, static
 directory again, as it was the case for
 http://hackage.haskell.org/platform/2010.1.0.0/haskell-platform.cabal
 and
 http://hackage.haskell.org/platform/2010.2.0.0/haskell-platform.cabal

Good idea.

 and the relationship between the repositories
 http://code.haskell.org/haskell-platform/ and
 http://code.galois.com/darcs/haskell-platform/ should be explained on
 http://trac.haskell.org/haskell-platform/.

That's just a temporary problem, since code.haskell.org was moved.

-- Don

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


[Haskell-cafe] Haskell Platform 2011.2.0.1 now available

2011-04-15 Thread Don Stewart
We're pleased to announce the 2011.2.0.1 release of the Haskell Platform:
a single, standard Haskell distribution for everyone.

Download the Haskell Platform 2011.2.0.1:

http://haskell.org/platform/

This release adds support for GHC 7.0.3, and significant improvements for
Mac OS X users.

The specification, along with installers (including Windows, Mac and
Unix installers for a full Haskell environment) are available.

The Haskell Platform is a single, standard Haskell distribution for
every system, in the form of a blessed library and tool suite for
Haskell distilled from the thousands of libraries on Hackage, along with
installers for a wide variety of systems. It saves developers work
picking and choosing the best Haskell libraries and tools to use for a
task.

When you install the Haskell Platform, you get the latest stable
compiler, an expanded set of core libraries, additional development
tools, and cabal-install – so you can download anything else you need
from Hackage.

This release ships with GHC 7.0.3.

What you get is specified here:

http://hackage.haskell.org/platform/contents.html

Thanks!

-- The Platform Infrastructure Team

P.S. a big thanks to Mark Lentczner and Mikhail Glushenkov who built the Mac
and Windows installers!

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


Re: [Haskell-cafe] Haskell Platform 2011.2.0.1 now available

2011-04-15 Thread Don Stewart
XCode 4 works, amongst other things:

http://www.haskell.org/ghc/docs/7.0.3/html/users_guide/release-7-0-3.html

Cheers,
   Don

On Fri, Apr 15, 2011 at 7:15 PM, Conal Elliott co...@conal.net wrote:
 This release adds support for GHC 7.0.3, and significant improvements for
 Mac OS X users.

 Enticing! What are these significant improvements for Mac OS X users?

   - Conal

 On Fri, Apr 15, 2011 at 3:44 PM, Don Stewart don...@gmail.com wrote:

 We're pleased to announce the 2011.2.0.1 release of the Haskell Platform:
 a single, standard Haskell distribution for everyone.

 Download the Haskell Platform 2011.2.0.1:

    http://haskell.org/platform/

 This release adds support for GHC 7.0.3, and significant improvements for
 Mac OS X users.

 The specification, along with installers (including Windows, Mac and
 Unix installers for a full Haskell environment) are available.

 The Haskell Platform is a single, standard Haskell distribution for
 every system, in the form of a blessed library and tool suite for
 Haskell distilled from the thousands of libraries on Hackage, along with
 installers for a wide variety of systems. It saves developers work
 picking and choosing the best Haskell libraries and tools to use for a
 task.

 When you install the Haskell Platform, you get the latest stable
 compiler, an expanded set of core libraries, additional development
 tools, and cabal-install – so you can download anything else you need
 from Hackage.

 This release ships with GHC 7.0.3.

 What you get is specified here:

    http://hackage.haskell.org/platform/contents.html

 Thanks!

 -- The Platform Infrastructure Team

 P.S. a big thanks to Mark Lentczner and Mikhail Glushenkov who built the
 Mac
 and Windows installers!

 ___
 Libraries mailing list
 librar...@haskell.org
 http://www.haskell.org/mailman/listinfo/libraries



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


Re: [Haskell-cafe] Current heap size and other runtime statistics -- API for accessing in GHC?

2011-04-10 Thread Don Stewart
I'd like a proper FFI binding for getting at Stats.c dynamically. So I
can write programs that determine their own stats about the GC and so
on.

On Sun, Apr 10, 2011 at 2:30 PM, Ryan Newton rrnew...@gmail.com wrote:
 Hi cafe,
 The rtsopts (-s etc) can provide some nice debugging information regarding
 memory management.  And System.Mem.performGC can initiate garbage
 collection.  But are there APIs for querying the current state of the heap?
  I've googled and come up dry.
 In this case I'm running benchmarks and for the sake of fair comparison I
 want to make sure that everything from a previous run is cleaned up before
 the next run.
 Thanks,
   -Ryan

 ___
 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] mtlx has a nice design but is slow

2011-04-06 Thread Don Stewart
Is the package missing some obvious inlining in the instances?

On Wed, Apr 6, 2011 at 10:13 AM, Sean Leather leat...@cs.uu.nl wrote:
 I just refactored my type and transform system prototype (introduced in [1]
 but changed since then) from using mtlx [2] (type-indexed monad transformers
 described in [3]) to mtl using RWST. mtlx allowed me to cleanly separate the
 various monadic components in a convenient way. Unfortunately, I found it to
 be too slow. The refactoring was an experiment to see how slow. I was rather
 surprised:

 Running time of a compiled main with a list of tests:
   mtlx (7 transformers): 2 min 52 sec
   mtl (RWST): 0 min 13 sec

 It's frustrating to see such a huge performance gap for a better design.

 Regards,
 Sean

 [1]
 http://splonderzoek.blogspot.com/2011/03/draft-type-changing-program-improvement.html
 [2] http://hackage.haskell.org/package/mtlx
 [3] http://www.ittc.ku.edu/~marks/cgi-bin/pubs/monadfactory.pdf


 ___
 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] How to contact OpenGL package maintainer (where is Sven?)

2011-04-06 Thread Don Stewart
Note, there are some issues, as this is a package in the Haskell
Platform, to do with upgrading and dependent packages. We should talk
first about issues there.

On Wed, Apr 6, 2011 at 2:32 PM, Jason Dagit dag...@gmail.com wrote:
 No response yet from Sven after about a month and no one seems to have heard
 from him in over a year.

 I'm going to take over for now under the assumption that Sven is missing.
 == My plans for moving forward ==
   * Assemble an opengl taskforce, a few people have already mentioned an
 interest in being on the team
   * clean up the current cabal files (I already wrote patches for that)
   * put the repos on github to make team collaboration easier
   * add the RULES that Andy Gill suggested for realToFrac
   * look at adding instances for MArray so that GLfloat et al can be stored
 in IOUArrays
   * add support for opengl 4.x
   * look at adding deprecation pragmas for deprecated opengl calls
   * new hackage releases
   * anything else that comes up
 Thanks,
 Jason

 On Sun, Mar 27, 2011 at 2:11 PM, Jason Dagit dag...@gmail.com wrote:

 I sent the message below to Haskell-Cafe about a week ago. I got one
 response saying that Sven has disappeared in the past but reappeared when
 updates were necessary.  I still haven't heard from Sven.  Now I'm widening
 my search.  My original email to Sven was on March 11th.
 It looks like the OpenGL packages on hackage[1,2,3,4] have not been
 updated in some time.  No updates later than Oct 2009.  I tried to email
 Sven directly using the email address listed on hackage but after over two
 weeks I still haven't heard from him.  I sent some patches to
 the opengl list about a week ago but I noticed that Sven hasn't posted on
 that list since Oct 2009 when he released the current version of OpenGLRaw.
  None of the public darcs repos have patches newer than Oct 2009.  Also, the
 homepage url listed in the packages is a 404:
 http://www.haskell.org/HOpenGL/
 My concern is that Sven has disappeared for some reason.  I hope he's
 well.  He has always done top notch work in the past maintaining these
 libraries.  Perhaps he's simply busy or lost interest?
 Does anyone know if he was looking for a new maintainer?  Perhaps you've
 heard from him more recently than Oct 2009?
 If a new maintainer is needed, I would consider nominating myself :)
 Thanks,
 Jason
 [1] http://hackage.haskell.org/package/OpenGLRaw
 [2] http://hackage.haskell.org/package/OpenGL
 [3] http://hackage.haskell.org/package/GLURaw
 [4] http://hackage.haskell.org/package/GLUT

 ___
 Libraries mailing list
 librar...@haskell.org
 http://www.haskell.org/mailman/listinfo/libraries



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


Re: [Haskell-cafe] mtlx has a nice design but is slow

2011-04-06 Thread Don Stewart
Typically you'll want to inline any definitions of = and return in
your classes and instances. Also, any non-recursive top level wrapper
functions.

On Wed, Apr 6, 2011 at 3:00 PM, Mark Snyder muddsny...@yahoo.com wrote:
 I'm the author for mtlx, and admittedly I didn't do anything about
 efficiency when I implemented it.  Is there any initial place I ought to
 look for tips on inlining? I'll start with the pragmas page
 (http://www.haskell.org/ghc/docs/7.0.3/html/users_guide/pragmas.html) I
 suppose.  I'm happy for any suggestions--optimizing hasn't been one of my
 focuses, so it's time for me to learn I suppose!
 I did switch to newtype definitions in the most recent version (0.1.5),
 which probably helped a lot compared to data definitions, but there are no
 inline pragmas in use, so perhaps there are some good opportunities for
 optimization.
 ~Mark Snyder

Is the package missing some obvious inlining in the instances?

 I just refactored my type and transform system prototype (introduced in
 [1]
 but changed since then) from using mtlx [2] (type-indexed monad
 transformers
 described in [3]) to mtl using RWST. mtlx allowed me to cleanly separate
 the
 various monadic components in a convenient way. Unfortunately, I found it
 to
 be too slow. The refactoring was an experiment to see how slow. I was
 rather
 surprised:

 Running time of a compiled main with a list of tests:
 ? mtlx (7 transformers): 2 min 52 sec
 ? mtl (RWST): 0 min 13 sec

 It's frustrating to see such a huge performance gap for a better design.

 Regards,
 Sean





 ___
 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 twidling modules

2011-03-13 Thread Don Stewart
Data.Binary or Data.Serialize perhaps? They provide encode/decode
functions for packing to binary formats:

 * cabal install binary
 * cabal install cereal

http://hackage.haskell.org/packages/archive/binary/0.5.0.2/doc/html/Data-Binary.html

On Sun, Mar 13, 2011 at 11:17 AM, rusi rustompm...@gmail.com wrote:
 I am not sure what would be the generic names I am asking for...
 examples are the nearest I can get.

 In perl there is pack/unpack http://perldoc.perl.org/perlpacktut.html
 Likewise in python there is struct module 
 http://docs.python.org/library/struct.html

 What is/are the Haskell equivalents?

 ___
 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] Light and fast http server

2011-03-11 Thread Don Stewart
snap or warp/yesod. maybe in a few years we will have a winner for the
platform...

--dons

On Friday, March 11, 2011, Vo Minh Thu not...@gmail.com wrote:
 2011/3/11 Victor Oliveira rhapso...@gmail.com:
 Hi cafe,

 There are a lot of http servers in hackage. I didn't have used none.
 I would like to know if one of them is something closer of the nginx.
 I need some light and fast. It don't need support all http, just the basics 
 is fine.
 Suggestions?

 Snap and Warp come to mind. Have a look at this reddit thread:
 http://www.reddit.com/r/programming/comments/flpao/the_haskell_high_performance_server_shootout/

 Cheers,
 Thu

 ___
 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] ANNOUNCE: Haskell Platform 2011.2 released!

2011-03-10 Thread Don Stewart
We're pleased to announce the 2011.2 release of the Haskell Platform: a
single, standard Haskell distribution for everyone.

Download the Haskell Platform 2011.2.0.0:

http://haskell.org/platform/

The specification, along with installers (including Windows, Apple and
Unix installers for a full Haskell environment) are available.

The Haskell Platform is a single, standard Haskell distribution for
every system, in the form of a blessed library and tool suite for
Haskell distilled from the thousands of libraries on Hackage, along with
installers for a wide variety of systems. It saves developers work
picking and choosing the best Haskell libraries and tools to use for a
task.

When you install the Haskell Platform, you get the latest stable
compiler, an expanded set of core libraries, additional development
tools, and cabal-install – so you can download anything else you need
from Hackage.

This release ships with GHC 7.

What you get is specified here:

http://hackage.haskell.org/platform/contents.html

Thanks!

-- The Platform Infrastructure Team

P.S. a big thanks to Mark Lentczner and Mikhail Glushenkov who built the Mac
and Windows installers!

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


Re: [Haskell-cafe] Haskell Platform 2011.2

2011-03-09 Thread Don Stewart
Also, due to reformatting code.haskell.org, the accounts were disabled
for a while.

On Wed, Mar 9, 2011 at 6:24 AM, Mark Lentczner mark.lentcz...@gmail.com wrote:
 code.haskell.org is the release repo
 code.galois.com is current development repo

 - Mark

 ___
 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] Haskell Platform web page is out of date

2011-03-09 Thread Don Stewart
We're about 1 day away from the release. Hold tight!!

-- Don (scramble scramble)

On Wed, Mar 9, 2011 at 1:21 PM, Paul Johnson p...@cogito.org.uk wrote:
 The Haskell Platform web page at http://hackage.haskell.org/platform// seems
 to need updating.  (Incidentally, that double slash at the end doesn't look
 right).

 * The next release is promised in Jan 2011.

 * The Release Timetable schedules the next release for 5 March 2011.

 I just worry that this is one of the first things someone investigating
 Haskell sees, and it creates a bad first impression.

 Paul.

 ___
 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] Haskell Platform 2011.2

2011-03-08 Thread Don Stewart
We have plenty of testers on the haskell-platform@ list. If you're
interested, you can join there to discuss results.
By definition the test installers are not yet ready for haskell-cafe@
consumption.

-- Don

On Tue, Mar 8, 2011 at 12:17 PM, Andrew Coppin
andrewcop...@btinternet.com wrote:
 On 06/03/2011 11:46 AM, Andrew Coppin wrote:

 On 06/03/2011 01:22 AM, Don Stewart wrote:

 P.S. you can help by testing the installers, and reporting issues on
 the HP trac and mailing list. The candidate installers are here:

 http://code.galois.com/darcs/haskell-platform/download-website/

 Is there some way to navigate to this page from the HP homepage?

 Seriously, if you want people to test it, having this fact more clearly
 visible seems like a good idea. (In particular, I have access to Windows
 systems I can test on, which is apparently rare around here, but until this
 email I had no idea that a release candidate was even available...)

 ___
 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] some problem with Cabal

2011-03-08 Thread Don Stewart
This is fixed in the new release of cabal-install  ( I think) so we're
rolling new installers.

Discussion around the installers is taking place on the haskell-platform list.

-- Don

On Wed, Mar 9, 2011 at 3:16 AM, Qi Qi qiqi...@gmail.com wrote:
 Hi,

 When I tried the haskell platform 2011.2 source, from here
 http://code.galois.com/darcs/haskell-platform/download-website/linux.html
 .

 Configuration passed successfully. But when making, it gives the following
 error:

 scripts/build.sh
 **
 Scanning system for any installed Haskell Platform components...

 Found:None.

 New packages to install: None! All done.

 **
 Building
 /usr/local/bin/ghc --make Setup -o Setup -package Cabal-1.10.1.0
 command line: cannot satisfy -package Cabal-1.10.1.0:
    Cabal-1.10.1.0-64e8f05722ea5bbdf07df2e5a3491105 is unusable due to missing 
 or recursive dependencies:
      directory-1.1.0.0-85d1d0f9d96dffdacf64f3cc6fba6f2f 
 process-1.0.1.5-4cab1bf0666275ac101dd48c7565b64c
    (use -v for more information)

 Error:
 Compiling the Setup script failed
 make: *** [build.stamp] Error 2


 I think this is the same problem as I got during installing some other
 packages via cabal such as hmatrix, ghc-mod, happy and etc.

 Does anyone have any idea about how to solve it?

 Thanks!



 --
 Qi Qi

 ___
 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] Benchmarks game updated

2011-03-05 Thread Don Stewart
Isaac Gouy from the Language Benchmarks game tells me that they're
starting to use GHC 7.0.2, there are a few tweaks, new flags (e.g. the
LLVM backend) and other experiments people might like to try.

Additionally, there are a couple of build failures that should be fixed.

http://shootout.alioth.debian.org/u64q/measurements.php?lang=ghc

-- Don

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


Re: [Haskell-cafe] Haskell Platform 2011.2

2011-03-05 Thread Don Stewart
We're currently testing the installers, with a view to announcing the
release early in the week.

Cheers,
  Don

P.S. you can help by testing the installers, and reporting issues on
the HP trac and mailing list. The candidate installers are here:

   http://code.galois.com/darcs/haskell-platform/download-website/

On Sat, Mar 5, 2011 at 4:39 PM, tsuraan tsur...@gmail.com wrote:
 The wiki page for Haskell Platform is still listing March 5 (today) as
 the planned release date.  Is this still the plan, or should the page
 be updated?

 ___
 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] ANN: unordered-containers - a new, faster hashing-based containers library

2011-02-22 Thread Don Stewart
bos:
On Sat, Feb 19, 2011 at 11:58 AM, Louis Wasserman
[1]wasserman.lo...@gmail.com wrote:
 
  size takes O(n).  That's just depressing.  Really.
 
That's rather thoughtless wording for some code that's (a) free (b) faster
than anything else currently available (c) in its very first release and
(d) available in source form for you to improve as you see fit. Just
depressing. Really.

Agreed. This is open source: patches or it stays at O(n).

-- Don

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


Re: [Haskell-cafe] linear and dependent types

2011-02-18 Thread Don Stewart
vigalchin:
Hello,
 
�� Does Haskell currently have support for linear types and dependent 
 types?

No.

-- Don 

P.S. :-)

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


Re: [Haskell-cafe] Headlines on haskell.org

2011-02-15 Thread Don Stewart
Just edit, its a wiki :-)

michael:
 Hi everyone,
 
 I'm not quite sure to whom to address this, but it is with regards to
 the Headlines section at the bottom of haskell.org. It has not been
 updated for 2011 yet, which I can't imagine looks very good to new
 users. Is anyone interested in/able to update it?
 
 If I may be so bold, I would like to offer up Warp as a possible
 headline. Are there any objections to this?
 
 Michael
 
 ___
 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] Gathering ideas for the Google Summer of Code

2011-02-13 Thread Don Stewart
Last year we worked hard to come up with a good list of projects for the
2010 Google Summer of Code. A  list drafted at ZuriHac is here:


http://donsbot.wordpress.com/2010/04/01/the-8-most-important-haskell-org-gsoc-projects/

And we ended up with quite a few of those funded,


http://donsbot.wordpress.com/2010/04/26/the-7-haskell-projects-in-the-google-summer-of-code/

Now is the time to think hard about student-sized projects that would be
valuable this year.

A great place to collect  these ideas, and discuss them, is the Haskell
Proposals Reddit,

http://www.reddit.com/r/haskell_proposals/

-- Don

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


Re: [Haskell-cafe] How large is the Haskell community ?

2011-02-12 Thread Don Stewart
aaronngray.lists:
I was wondering if anyone had an idea or estimate as to how large the
Haskell community is ?

No one knows. There are many figures that you could use to estimate the
size (e.g. I try to gather signifcant stats in yearly reports about
Hackage)

 * In 2010, for example, 138,000 unique IPs downloaded the Haskell Platform.

http://www.galois.com/~dons/talks/hiw-hackage-y2.pdf

-- Don

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


Re: [Haskell-cafe] How large is the Haskell community ?

2011-02-12 Thread Don Stewart
aaronngray.lists:
Then there are people who download it, look at it and maybe find it too
complex to use ?�
I am wondering if mailing list statistics would be the best guide ?

Many people don't subscribe to the mailing list, and instead read it on
gmane, or google, or reddit, or follow the stackoverflow site, or ...

E.g. 6500 people follow Haskell on Reddit. How many Haskellers don't
feel the need to read daily news about it?

-- Don


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


Re: [Haskell-cafe] Data.ByteString.Lazy.ByteString vs Data.ByteString.Lazy.Internal.ByteString

2011-02-10 Thread Don Stewart
ckkashyap:
Hi,
I noticed that even though I declare the type of a function in my code as�
Data.ByteString.Lazy.ByteString ... when I check it out in ghci using :t,
it shows this -�Data.ByteString.Lazy.Internal.ByteString
Is this expected?

Yep, the 'Internal' module is where the type is defined, and then
re-exported through the regular module.

All is well.

-- Don

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


Re: [Haskell-cafe] ($) not as transparent as it seems

2011-02-03 Thread Don Stewart
catamorphism:
 On Thu, Feb 3, 2011 at 12:44 PM, Steffen Schuldenzucker
 sschuldenzuc...@uni-bonn.de wrote:
 
  Dear cafe,
 
  does anyone have an explanation for this?:
 
  error (error foo)
  *** Exception: foo
 
  error $ error foo
  *** Exception: *** Exception: foo
 
 
 Have you read the intermediate Core (using -ddump-simpl) for each variation?
 

A.
GHC.Base.bindIO
  @ GHC.Prim.Any
  @ [()]
  ((GHC.Err.error @ [GHC.Types.Char] (GHC.Base.unpackCString# foo))
   `cast` (CoUnsafe [GHC.Types.Char] (GHC.Types.IO GHC.Prim.Any)
   :: [GHC.Types.Char] ~ GHC.Types.IO GHC.Prim.Any))
  ((\ (it_ade :: GHC.Prim.Any)
  (eta_B1 :: GHC.Prim.State# GHC.Prim.RealWorld) -
  ((GHC.Base.returnIO
  @ [()]
  (GHC.Types.:
 @ ()
 (it_ade `cast` (CoUnsafe GHC.Prim.Any () :: GHC.Prim.Any ~ ()))
 (GHC.Types.[] @ (
   `cast` (GHC.Types.NTCo:IO [()]
   :: GHC.Types.IO [()]
~
  (GHC.Prim.State# GHC.Prim.RealWorld
   - (# GHC.Prim.State# GHC.Prim.RealWorld, [()] #
eta_B1)
   `cast` (GHC.Prim.Any - sym (GHC.Types.NTCo:IO [()])
   :: (GHC.Prim.Any
   - GHC.Prim.State# GHC.Prim.RealWorld
   - (# GHC.Prim.State# GHC.Prim.RealWorld, [()] #))
~
  (GHC.Prim.Any - GHC.Types.IO [()])))

B.
GHC.Base.bindIO
  @ GHC.Prim.Any
  @ [()]
  (GHC.Base.$
 @ [GHC.Types.Char]
 @ (GHC.Types.IO GHC.Prim.Any)
 (GHC.Err.error @ (GHC.Types.IO GHC.Prim.Any))
 (GHC.Err.error @ [GHC.Types.Char] (GHC.Base.unpackCString# foo)))
  ((\ (it_aib :: GHC.Prim.Any)
  (eta_B1 :: GHC.Prim.State# GHC.Prim.RealWorld) -
  ((GHC.Base.returnIO
  @ [()]
  (GHC.Types.:
 @ ()
 (it_aib `cast` (CoUnsafe GHC.Prim.Any () :: GHC.Prim.Any ~ ()))
 (GHC.Types.[] @ (
   `cast` (GHC.Types.NTCo:IO [()]
   :: GHC.Types.IO [()]
~
  (GHC.Prim.State# GHC.Prim.RealWorld
   - (# GHC.Prim.State# GHC.Prim.RealWorld, [()] #
eta_B1)
   `cast` (GHC.Prim.Any - sym (GHC.Types.NTCo:IO [()])
   :: (GHC.Prim.Any
   - GHC.Prim.State# GHC.Prim.RealWorld
   - (# GHC.Prim.State# GHC.Prim.RealWorld, [()] #))
~
  (GHC.Prim.Any - GHC.Types.IO [()])))


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


Re: [Haskell-cafe] Haskell Platform 2011.x - planned release date?

2011-02-01 Thread Don Stewart
Due to lack of time, I've been unavailable. I expect the release to come
out around Feb 11, during the BayHac hackathon.

Apologies for the delay.

-- Don

mxcantor:
 January has come and gone and HP 2011 has not come with it.  Is there
 an updated timetable for the next version of the HP?  I'm not
 complaining or upset or whining, just trying to plan.  
 
 Great work so far, looking forward to HP 2011!
 
 mc
 ___
 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] Merging SMT solving and programming languages: two EDSLs for SMT in Haskell

2011-01-18 Thread Don Stewart
Hey all,

For a while now, Galois has been interested in connecting automated solvers to
our programming language of choice, Haskell, to make it possible to prove
automatically some properties of our functions (rather than just testing, e.g.
with QuickCheck). We've pushed two efforts out this week, as previews of what
we're thinking in this space:

 * SBV; and
http://hackage.haskell.org/package/sbv

 * yices-painless.
http://hackage.haskell.org/package/yices-painless

Both are embedded DSLs for representing propositions to an SMT solver via
Haskell functions and values. They take different approaches (a compiler from
Haskell to the SMT-LIB format, versus an interpreter for the Yices SMT solver).
SBV is the more mature package, while yices-painless emphasizes a
type-preserving translation from a minimal core language. SBV was built by
Levent Erkok, yices-painless by Don Stewart. Documentation for the design of
yices-painless is available, as is documentation on SBV.

Both are ready for experimentation and feedback, and we welcome your comments.

More information is on the blog:


http://corp.galois.com/blog/2011/1/18/merging-smt-solvers-and-programming-languages.html

-- Don

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


[Haskell-cafe] Fwd: [TYPES/announce] Oregon Programming Languages Summer School]

2011-01-12 Thread Don Stewart

This will be of interest to many Haskellers. The line up is always
outstanding, Oregon is lovely in the summer, and you can drop by Galois
while you're here :-)

-- Don

- Forwarded message from Robert Harper r...@cs.cmu.edu -

Date: Wed, 12 Jan 2011 16:49:46 -0500
From: Robert Harper r...@cs.cmu.edu
To: types-annou...@lists.seas.upenn.edu
Cc: pierre-louis curien eu.sunt.pica...@gmail.com
Subject: [TYPES/announce] Oregon Programming Languages Summer School

[ The Types Forum (announcements only),
http://lists.seas.upenn.edu/mailman/listinfo/types-announce ]

We are pleased to announce the preliminary program for the 10th annual  
Oregon Programming Languages Summer School (OPLSS) to be held 15 June to 1 
July 2011 at the University of Oregon in Eugene.  This year's program is 
titled Types, Semantics, and Verification, and features the following 
speakers:

Amal Ahmed   Logical relations
Indiana University

Andrew Appel   Software verification
Princeton University

Nick Benton Monadic effects
Microsoft Research

Robert Constable
Cornell University

Pierre-Louis Curien  Polarization and Focalization
pi.r2 team, PPS, CNRS-Paris 7 University-INRIA

Robert Harper  Type theory foundations
Carnegie Mellon University

Hugo HerbelinFoundation of Coq
pi.r2 team, PPS, CNRS-Paris 7 University-INRIA

Xavier Leroy  Compiler verification
INRIA

Paul-Andre' Mellies   Category theory
pi.r2 team, PPS, CNRS-Paris 7 University-INRIA

Greg Morrisett Ynot programming
Harvard University

Frank PfenningProof theory foundations
Carnegie Mellon University

Benjamin Pierce Software foundation in Coq
University of Pennsylvania

Dana Scott
Carnegie Mellon University

Full information on registration will be available shortly at 
http://www.cs.uoregon.edu/Activities/summerschool/summer11.

Robert Harper
Zena Ariola
Pierre-Louis Curien


- End forwarded message -

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


Re: [Haskell-cafe] Misleading MVar documentation

2010-12-24 Thread Don Stewart
ezyang:
 Merry Christmas all!
 
 Is it just me, or does the Control.Concurrent.MVar documentation seem a bit
 misleading?  In particular, we should explicitly note the race conditions
 for not just swapMVar but also readMVar, withMVar, modifyMVar_ and modifyMVar,
 and clarify that the safety guarantees of the latter three pertain to their
 handling of asynchronous exceptions.
 
 It might also be good to tell people that if they need race-free operations
 of this style, STM is a good alternative to look at, even if only one variable
 is being synchronized over.
 

That would be a good contribution.

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


Re: [Haskell-cafe] Latest Haskell Platform for Windows

2010-12-22 Thread Don Stewart
aaronngray.lists:
Could someone please point me at a copy of the latest Haskell platform or
a working GHC please.
Many thanks in advance,

The links on haskell.org/platform should work (there was a domain
change, so you'll no longer see lambda.galois.com links).

-- Don

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


Re: [Haskell-cafe] Recent Package Updates on Haskell.org

2010-12-11 Thread Don Stewart
gabrielp:
 Is it just me or has the list of recent package updates, as seen on the
 front page of haskell.org, not changed since the migration?

That's right. I have to tweak the tool a little bit for the new format.

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


Re: [Haskell-cafe] Trying out GHC 7

2010-12-06 Thread Don Stewart
 andrewcoppin:

[100 lines snipped]

Andrew, if you have a bug report, please use the bug tracker:

http://hackage.haskell.org/trac/ghc/wiki/ReportABug

Keep your reports concise and to-the-point, for the best hope of getting
useful stuff done.

Cheers,
  Don

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


Re: [Haskell-cafe] the beginning of the end (was: Hackage down?)

2010-12-04 Thread Don Stewart
trebla:
 On 10-12-04 01:03 PM, Antoine Latter wrote:
 Here's a Reddit post:
 http://www.reddit.com/r/haskell/comments/efw38/reminder_hackagehaskellorg_outage_tomorrow_due_to/

 This is the second consecutive time a planned downtime is not announced  
 on either mailing lists.

 This seems to me planned obsoletion of the mailing lists.
 http://article.gmane.org/gmane.comp.lang.haskell.cafe/82673

 For now, if a web 2.0 source I care enough about provides RSS, I make do  
 with adding it to Google Reader, which provides mark-as-read and  
 show-all-and-only-those-unread as perfectly as long-existing email 
 programs.


You can get a feed of haskell.org announcements here:

http://twitter.com/statuses/user_timeline/216043045.rss

Particularly when the mailing lists are down (e.g. due to server
migration), cloud-hosted services have proven invaluable for getting the
word out.

-- Don

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


Re: [Haskell-cafe] Downloading web page in Haskell

2010-11-20 Thread Don Stewart
michael:
 2010/11/20 José Romildo Malaquias j.romi...@gmail.com:
  In order to download a given web page, I wrote the attached program. The
  problem is that the page is not being full downloaded. It is being
  somehow intettupted.
 
  Any clues on how to solve this problem?
 
 My guess is that there's a character encoding issue. Another approach
 would be using the http-enumerator package[1]. The equivalent program
 is:
 
 module Main where
 
 import Network.HTTP.Enumerator (simpleHttp)
 import qualified Data.ByteString.Lazy as L
 
 main =
   do src - simpleHttp
 http://www.adorocinema.com/common/search/search_by_film/?criteria=Bourne;
  L.writeFile test.html src
  L.putStrLn src
 


FWIW, with this url, I get the same problem using the Curl package (via the 
download-curl):

import Network.Curl.Download
import qualified Data.ByteString as B

main = do
edoc - openURI 
http://www.adorocinema.com/common/search/search_by_film/?criteria=Bourne;
case edoc of
Left err  - print err
Right doc - B.writeFile test.html doc
 

Not a problem on e.g. http://haskell.org

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


[Haskell-cafe] Announcement: the Haskell.org committee has formed

2010-11-15 Thread Don Stewart

= The haskell.org committee has formed =

http://haskellorg.wordpress.com/2010/11/15/the-haskell-org-committee-has-formed/

In recent years, haskell.org has started to receive assets, e.g. Google
Summer Of Code funds, donations for Hackathons, and a Sparc machine for
use in GHC development. We have also started spending this money: on the
community server, on a server to take over hosting haskell.org itself,
and on the haskell.org domain name. There is also interest in running
fundraising drives for specific things such as Hackathon sponsorship and
hosting fees.

To resolve who is responsible for haskell.org’s infrastructure
development, open nominations were held to form a haskell.org committee,
based on representatives from the open source Haskell community.
Nominations were received, and we are pleased to announce that the new
committee has formed.

The current members of the committee are:

  • Don Stewart [chair]
  • Edward Z. Yang
  • Ganesh Sittampalam
  • Ian Lynagh
  • Johan Tibell
  • Malcolm Wallace
  • Vo Minh Thu

Members are expected to serve a 3 year term, and terms are staggered so
that 2 or 3 members step down each year.

= What we’re working on =

Over the past year, two of the core infrastructure nodes:
www.haskell.org (which hosts the main wiki), and code.haskell.org (which
hosts a lot of project repositories) have become increasingly
unreliable. To address this, a new high-spec, dedicated host was
purchased, which will be used to replace both services.

The commitee is now working directly to solve these issues:

  • Moving www.haskell.org (and the mailing lists) from Yale to the new 
dedicated host.
  • Migrating the code.haskell.org host to a VM on the new machine.

More news on this work shortly.

= Stay up to date =

To help people better keep up to date on the status of the haskell.org
infrastructure, stay up to date via:

  • Online: http://haskellorg.wordpress.com/ 

  • Twitter:http://twitter.com/haskellorg 
- get status updates about haskell.org services via twitter.

  • Email:  commit...@haskell.org
- To get in touch with the committee, use the committee @ haskell.org 
address.

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


Re: [Haskell-cafe] http://functionalley.eu

2010-11-06 Thread Don Stewart
haskellcafe:
 I've just written a few packages which I think may be useful, and have made
 them available as free opensource on a personal website 
 http://functionalley.eu

Wonderful, thank you!

 I opted to host them there rather than  uploading them to Hackage, because
 they're part of a wider project.

Note that this means they won't be cabal installable or searchable. Was
that your intention?

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


Re: [Haskell-cafe] http://functionalley.eu

2010-11-06 Thread Don Stewart
claus.reinke:
 I opted to host them there rather than  uploading them to Hackage,  
 because
 they're part of a wider project.

 Note that this means they won't be cabal installable or searchable. Was
 that your intention?

 I am curious about this: wasn't cabal designed with the
 option of having several package repos in mind?

please clarify/document --remote-repo
http://hackage.haskell.org/trac/hackage/ticket/759


It supports remote Hackage repositories -- not arbitrary URLs (though
that is planned). Search won't work though.

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


Re: [Haskell-cafe] Finding the contents of haskell platform?

2010-11-05 Thread Don Stewart
dons:
 magnus:
  I know there's a .cabal file for the latest version of HP somewhere,
  but I can't coerce Google into finding me a link that actually works.
  Furthermore, the following page:
  
  http://hackage.haskell.org/platform/contents.html
  
  does list all the contents, but to my big surprise it doesn't link to
  the specific versions of the packages for HP, instead it links to the
  latest version found on Hackage.
  
 
 I'll generate a spec page from the .cabal file this week sometime.
 

The changelog now lists all the versions:

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


Re: [Haskell-cafe] Who manages http://hackage.haskell.org/trac/?

2010-11-05 Thread Don Stewart
simons:
 Hi guys,
 
 a while ago, I created an account on Trac. Now, it seems that I've forgotten
 both the password and the e-mail address that I used at the time. I cannot
 log in, and I cannot make Trac send me the password either. Clearly, I need
 the help of a human being with administrator privileges to figure that out.
 
 Can someone give me a pointer about who I'd want to contact regarding that
 issue?
 

Ian Lynagh manages these community resources as a member of the
Haskell.org infrastruture team.

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


Re: [Haskell-cafe] Finding the contents of haskell platform?

2010-11-01 Thread Don Stewart
magnus:
 I know there's a .cabal file for the latest version of HP somewhere,
 but I can't coerce Google into finding me a link that actually works.
 Furthermore, the following page:
 
 http://hackage.haskell.org/platform/contents.html
 
 does list all the contents, but to my big surprise it doesn't link to
 the specific versions of the packages for HP, instead it links to the
 latest version found on Hackage.
 
 Would someone with the power to make changes on the HP pages *please*
 make it as easy as possible to find the *exact* specification of what
 HP contains?  Please, pretty please with sugar on top.
 
 No, a changelog entry
 (http://hackage.haskell.org/platform/changelog.html) is not very
 helpful (why the HP front page links to it I can't understand).
 
 Going via the Haskell wiki
 (http://www.haskell.org/haskellwiki/Haskell_Platform#What.27s_in_the_platform)
 to find a link to the .cabal
 (http://code.haskell.org/haskell-platform/haskell-platform.cabal) is
 not that user friendly.  It's even worse that the latter link doesn't
 seem to work at all at the moment.
 
 (The short irritated tone in this email accurately shows my
 desperation with the situation: I thought I would be able to find this
 information with only 5 minutes to spare before my next meeting.)
 

Currently, the versions are specified in the .cabal file.
A script is used to generate the changelog page (diffcabal, iirc).

I'll generate a spec page from the .cabal file this week sometime.

-- Don

P.S. better sent to the haskell-platform@ list


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


Re: [Haskell-cafe] fundata1 -- Karmic Social Capital Benchmark and Shootout

2010-10-29 Thread Don Stewart
dmehrtash:
 In the lessons you say:
 
 
 Haskell proved too slow with String Map, so we ended up interning strings
 and working with an IntMap and a dictionary to disintern back to strings 
 as
 a last step.  Daniel Fisher was instrumental in bringing Haskell up to
 speed with OCaml and then beating it.  Don Stewart provided awesome
 leadership and amazing modification of Haskell's core data structured
 before your very eyes.
 
 
 
 Can you elaborate on this?
 
 and What do you mean by: modification of Haskell's core data structured  ?

I think he means some of the stuff Daniel and I did with specializing
data structures (like IntMap) to their monomorphic key / elem types.

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


Re: [Haskell-cafe] Edit Hackage

2010-10-29 Thread Don Stewart
ivan.miljenovic:
 Neither the Haskell reddit nor Stack Overflow are linked to from
 haskell.org and there is nothing to indicate that they are official.
  Also, wasn't it Don that started (and is mainly responsible) for
 linking to Haskell articles on reddit?
 

They're linked from the front page.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Edit Hackage

2010-10-29 Thread Don Stewart
ivan.miljenovic:
 On 30 October 2010 09:51, Don Stewart d...@galois.com wrote:
  ivan.miljenovic:
  Neither the Haskell reddit nor Stack Overflow are linked to from
  haskell.org and there is nothing to indicate that they are official.
   Also, wasn't it Don that started (and is mainly responsible) for
  linking to Haskell articles on reddit?
 
 
  They're linked from the front page.
 
 Huh, so they are; shows how long it has been since I looked at the
 front page.  We just need to get haskellers.com listed there now...

I added them in about Nov 2008, FWIW.

http://haskell.org/haskellwiki/?title=Template:Main/Communityoldid=24203
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Edit Hackage

2010-10-28 Thread Don Stewart
gcross:
 On 10/28/10 12:34 PM, Andrew Coppin wrote:
 More specifically, I copied the Cabal description from another package  
 and then updated all the fields. Except that I forgot to update one.  
 And now I have a package which I've erroneously placed in completely  
 the wrong category.

 I am glad to hear that I am not the only one who has done this.  :-)  I  
 second the notion that it would nice to be able to tweak the meta-data  
 of a package after uploading it.


Status of Infrastructure questions like this are best asked on the
Haskell Reddit.

http://www.reddit.com/r/haskell/search?q=hackagerestrict_sr=onsort=new

In fact, there was a recent announcement about this:

http://cogracenotes.wordpress.com/2010/08/14/policy-on-hackage-server/

Where you can edit tags live on the new server.

-- Don

P.S. I encourage people to use the online forums: Haskell Reddit and Stack
Overflow, as a lot of the question-answering activity has shifted there
now, away from -cafe@

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


Re: [Haskell-cafe] Edit Hackage

2010-10-28 Thread Don Stewart
stephen.tetley:
 On 28 October 2010 20:59, Don Stewart d...@galois.com wrote:
 
  Status of Infrastructure questions like this are best asked on the
  Haskell Reddit.
 
 [SNIP]
 
  P.S. I encourage people to use the online forums: Haskell Reddit and Stack
  Overflow, as a lot of the question-answering activity has shifted there
  now, away from -cafe@
 
 Err, Why?

The online services provide searchable content, tagging, and the ability
to rate, edit and refer to previous content.  E.g.

http://stackoverflow.com/questions/tagged/haskell?sort=hotpagesize=15
  
 Having to track three places for information rather than one doesn't
 seem like a good swap to me...

It's too late.

The number of subscribers to the Haskell Reddit, for example, is double
the -cafe@, and there are comparable numbers of questions being asked on
the Stack Overflow [haskell] tag, as here -- so anyone who only reads
-cafe@ is already missing a lot of stuff.

A lot of the community has already voted on the efficacy of mailing
lists for large communities, by moving their discussion elsewhere.

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


Re: [Haskell-cafe] Haskell and a complete mail client lib?

2010-10-27 Thread Don Stewart
gue.schmidt:
 Hi all,

 do we Haskellers have a complete Mail client library?

As always, look on Hackage:


http://www.google.com/search?hl=enas_sitesearch=hackage.haskell.org/packageas_q=email
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec in Haskell platform

2010-10-24 Thread Don Stewart
andrewcoppin:
 On 24/10/2010 09:10 AM, Roman Cheplyaka wrote:
 It would be convenient to have a page which would list all the HP packages
 with their versions. The release page [2] only has a list of packages
 whose versions has changed since the last release, as I understood.

 It would be nice to have a page that lists everything included in every  
 HP release, together with their version numbers. (So that, e.g., I can  
 see at a glance what version of GHC, Haddock or cabal-install is in  
 HP-2009.1.0.0.) All this information must exist somewhere, it's just not  
 easily viewable on the web.

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


  1   2   3   4   5   6   7   8   9   10   >