Re: [Haskell-cafe] Observations from ListLike

2007-09-18 Thread Ketil Malde
On Mon, 2007-09-17 at 14:37 -0500, John Goerzen wrote:

 * It would be really nice if QuickCheck supported I/O and some version
   of HUnit's TestLabel to generate hierarchical names when failures
   occur.

I've done this for testing IO (reading and writing files):

 prop_serialize (E s) = 
let [s'] = unsafePerformIO (do writeFasta /tmp/serialize_test [s]
   readFasta /tmp/serialize_test)
in s == s'

I'm not sure if this is kosher, but at least the tests pass :-)

I (like everybody else?)'ve written a small driver for the tests, but
perhaps I should look at HUnit for a more general framework?

-k

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


Re: [Haskell-cafe] Building production stable software in Haskell

2007-09-18 Thread Ketil Malde
On Tue, 2007-09-18 at 01:11 +0100, Neil Mitchell wrote:

 DBM's can differentiate themselves on external database support,

Surely this is an opportunity to focus development on a single library
with broader support?  Currently, we have HSQL and HDBC supplying
incompatible low-level interfaces, supporting a different set of back
ends.  No matter what I choose, I risk having to make a costly
conversion later on.

 XML is not simple and does not interface to third
 party programs. I can think of at least 4 XML libraries, all of which
 are quite different. 

...and at least some of them come with their own re-implementation of
Data.Tree.

I think competition and choice can be great, but I also think it is
important to have a good default libraries to turn to for, well,
production stable software.

-k

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


[Haskell-cafe] Library Process (was Building production stable software in Haskell)

2007-09-18 Thread Dominic Steinitz
This discussion has sparked a question in my mind:

What is the process for the inclusion of modules / packages in ghc, hugs and 
other compilers  interpreters?

I thought the master plan was that less would come with the compiler / 
interpreter and the user would install packages using cabal.

I was thus mildly surprised earlier this year to find e.g. data.bytestring was 
included with ghc. Now that I look at the haddock, it says this is a base 
package but doesn't say anything about its status. On the other hand, there 
are lots of modules that are base packages that are experimental. Should 
something experimental be a base package? And shouldn't all modules that are 
base packages declare their status?

Perhaps these are questions for the libraries mailing list but I thought I'd 
start here.

Yours confused of Kingston.

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


[Haskell-cafe] Re: Building production stable software in Haskell

2007-09-18 Thread apfelmus

Ketil Malde wrote:

Neil Mitchell wrote:


DBM's can differentiate themselves on external database support,


Surely this is an opportunity to focus development on a single library
with broader support?  Currently, we have HSQL and HDBC supplying
incompatible low-level interfaces, supporting a different set of back
ends.  No matter what I choose, I risk having to make a costly
conversion later on.


Yes, a common low-level interface is highly recommended. This does not 
only hold for DBMs, but also for XML, GUIs, vector graphics etc. The 
(imaginary, I'm a DB illiterate) picture is this:


 HDB -+ +--- Borland
  | |
 LambdaBase --+--- Generic Low-level DB --- +--- Oracle
  | |
 hasqel --+ +--- MySQL
  | |
 ...   ...

A common low-level interface factors the m - n relation into a m - 1 
and a 1 - n relation.


The story doesn't end here, since there can be additional low-level 
functionality that only some DB backends can offer but that some 
high-level interfaces require. But that's just a matter of putting 
another type class on top of the minimal low-level type class.


Of course, designing a low-level interface that is neither too powerful 
(not all back ends offer the functionality) nor too general (being 
almost trivial) and still simple enough is *hard*, especially since you 
can think about it for weeks without touching a computer.


Regards,
apfelmus

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


RE: [Haskell-cafe] How can I stop GHCi from calling show for IO actions?

2007-09-18 Thread Simon Peyton-Jones


| -Original Message-
| From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Sam
| Hughes
| Sent: 16 September 2007 04:53
| To: Ryan Ingram
| Cc: haskell-cafe
| Subject: Re: [Haskell-cafe] How can I stop GHCi from calling show for IO 
actions?
|
| Ryan Ingram wrote:
|  Prelude let inf = repeat 1
|  Prelude inf
|  [1,1,(lots of output until I press ctrl-c),Interrupted.
|  (I expect this to happen)
|  Prelude let x = inf
|  (no output here!)
|  Prelude :t x
|  x :: [Integer]
|  Prelude return inf
|  [1,1,(lots of output until I press ctrl-c),Interrupted.
|  (I also expect this to happen)
|  Prelude y - return inf
|  [1,1,(lots of output until I press ctrl-c),Interrupted.
|  (I do not expect this to happen here!)
|  Prelude :t y
| 
|  interactive:1:0: Not in scope: 'y'
| 
|  Is this a bug?  Why does y - return exp have different behavior
|  than let y = exp?  Is there a way to make GHCi not print the result
|  of an action but still make my variables get bound?
|
| That's weird.
|
| Prelude (x,y) - return $ (repeat 1, repeat 2)
| Prelude Just x - return $ Just (repeat 1)
| [1,1,1,...
| Prelude (x,_) - return $ (repeat 1, repeat 2)
| [1,1,1,...
| Prelude Just (x,y) - return $ Just (repeat 1, repeat 2)
| Prelude
|
| It seems that GHCi outputs the contents of the variable you've created
| when there's only one of them.

Indeed, that is documented behaviour (first bullet here:
http://www.haskell.org/ghc/docs/latest/html/users_guide/ch03s04.html#ghci-stmts
)

Perhaps it's confusing behaviour?  If so do suggest an alternative.

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


[Haskell-cafe] Re: Israel Haskell Programmers

2007-09-18 Thread Alex Strugatsky
On 2007-09-16, B K [EMAIL PROTECTED] wrote:
 Hello,
 Are there any Haskell Hackers on this mailing list who live in Israel?
 I am interested in starting an Israel Haskell User Group.

Hi, 
I'll be glad to join.

Besides, I'll be glad to here from an Israel Haskell hacker
who maybe interested in a Haskell job in the North area (Nahariyya).

Alex


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


[Haskell-cafe] Re: Type-Marking finite/infinte lists?

2007-09-18 Thread apfelmus

Bas van Dijk wrote:

Roberto Zunino wrote:



data Z
data S n
data List a len where
   Nil :: List a Z
   Cons:: a - List a len - List a (S len)




The other day I was playing with exactly this GADT. See: http://hpaste.org/2707

My aim was to define a function like 'concat' in terms of 'foldr' but
I was unable to do so. Can this be done?


Not with the standard foldr you mimic. I mean, in reality, foldr is 
(almost) the induction principle for natural numbers! Given a property 
p  that you want to prove for all natural numbers  n , the induction 
principle reads


  induction :: forall p .
(forall n . p n - p (S n)) -- induction step
 - p Z -- induction base
 - (forall n . p n)-- it holds!

Similarly, the right type of foldr is

  foldr :: forall b a .
 - (forall n . a - b n - b (S n))
 - b Z
 - (forall n . List a n - b n)

or without the superfluous foralls

  foldr :: (forall n . a - b n - b (S n)) - b Z - List a n - b n

The implementation is exactly the same

  foldr _ z Nil = z
  foldr f z (Cons x xs) = f x (foldr f z xs)

Put differently, you just add the length parameter to b.


For concat, we have to set

  b n = List a (Sum n m)

Given only  List a (Sum n m), the Haskell type checker can't figure out 
that it is of the form  b n  for some type constructor  b  . The 
solution is to introduce a newtype to guide it


  newtype PlusList a m n = In { out :: List a (Sum n m) }

so that we now have b = (PlusList a m) and we can write

  concat :: forall a m n . List a n - List a m - List a (Sum n m)
  concat xs ys = out (foldr f z xs)
where
f :: a - PlusList a m n - PlusList a m (S n)
f x b = In (cons x (out b))
z :: PlusList a m Z
z = In ys

I didn't test this code, but it should work ;)


Also I was unable to define the function 'fromList :: [a] - ListN a
n'. This makes sense of course because statically the size of the list
is unknown. However maybe existential quantification can help but I'm
not sure how.


The return type of  fromList  can't be

  fromList :: [a] - List a n

since that's syntactic sugar for

  fromList :: forall n . [a] - List a n

i.e. given a list, fromList  returns one that has all possible lengths 
n. Rather, the type should be


  fromList :: [a] - (exists n . List a n)

i.e. there exists a length which the returned list has. (Exercise: why 
is  (exists n . [a] - List a n)  wrong?)


The data type  ListFinite  from my other message on this thread does the 
existential quantification you want. With


  nil  :: ListFinite a
  nil  = IsFinite (Nil)

  cons :: a - ListFinite a - ListFinite a
  cons x (IsFinite xs) = IsFinite (Cons x xs)

we can write

  fromList :: [a] - ListFinite a
  fromList [] = nil
  fromList (x:xs) = cons x (fromList xs)


Regards,
apfelmus

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


Re: [Haskell-cafe] Library Process (was Building production stable software in Haskell)

2007-09-18 Thread Malcolm Wallace
Dominic Steinitz [EMAIL PROTECTED] wrote:

 I thought the master plan was that less would come with the compiler /
 interpreter and the user would install packages using cabal.

Ideally, yes.  I think a useful model would be GNU/Linux, where there is
the Linux kernel, developed by core hackers, and then there are
distributions, which package up particular kernels with a load of
different GNU libraries and utilities to form a complete operating
environment.  The maintainers of the distributions do not work on the
kernel, but they do test their own combinations of kernel/libraries +
utilities to ensure that everything plays together nicely.

I would like to see the same separation forming between the ghc compiler
itself (which would minimally include only the small number of libraries
needed to build the compiler), and larger distributions which would be
maintained by other people, and include much larger collections of
packages that the maintainer has tested and verified to work together.
In the best of all worlds, a Haskell distribution would include
multiple compilers, not just ghc.

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


Re: [Haskell-cafe] Observations from ListLike

2007-09-18 Thread Malcolm Wallace
John Goerzen [EMAIL PROTECTED] wrote:

 * Hugs programs that use cpphs can't use ByteString

This bug in cpphs was fixed already, several days ago.

 * It would be really nice if QuickCheck supported I/O

QuickCheckM gives you monadic test properties, as described in a Haskell
Workshop 2002 paper.
http://www.cs.chalmers.se/~rjmh/QuickCheck/

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


Re: [Haskell-cafe] Library Process (was Building production stable software in Haskell)

2007-09-18 Thread Neil Mitchell
Hi

 What is the process for the inclusion of modules / packages in ghc, hugs and
 other compilers  interpreters?

Propose to have the packaged added. There is a very low chance of this
being accepted. The only packages to have recently been added were
FilePath and ByteString, both of which were obvious deficiencies in
the libraries. I'm now not aware of any hole that is likely to get
plugged by bundling an additional library.

 Should
 something experimental be a base package? And shouldn't all modules that are
 base packages declare their status?

No, they should all be reasonably stable. Things that are unstable are
likely to move out of the standard libraries and just become hackage
packages.

 Perhaps these are questions for the libraries mailing list but I thought I'd
 start here.

Now there is a question I can't answer - I have no idea what should go
down the libraries list and what should go down the haskell-cafe list.
Perhaps someone could put up a guide of if your question/comment is
like this, send it on this list

Thanks

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


[Haskell-cafe] unique id for data types

2007-09-18 Thread Barney Hilken
In order to make my records system practically useable, I need a type  
family


type family NameCmp n m

which totally orders datatypes. More precisely, it should return one  
of the

following types:

data NameLT = NameLT
data NameEQ = NameEQ
data NameGT = NameGT

for each pair of datatypes n  m, according to whether n  m, n = m,  
or n  m
in some global ordering. This ordering needs to be independent of the  
context,
so it can't be affected by whatever imports there are in the current  
module.


What I want to know is: does GHC give datatypes any global id I could  
use to

generate such an ordering? Would fully qualified names work?

Secondly (assuming it's possible) how easy would it be for me to  
write a patch

to add NameCmp to GHC? Where in the source should I start looking?

Thanks,

Barney.


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


Re: [Haskell-cafe] Library Process (was Building production stable software in Haskell)

2007-09-18 Thread Adrian Hey

Neil Mitchell wrote:

Hi


What is the process for the inclusion of modules / packages in ghc, hugs and
other compilers  interpreters?


Propose to have the packaged added. There is a very low chance of this
being accepted. The only packages to have recently been added were
FilePath and ByteString, both of which were obvious deficiencies in
the libraries. I'm now not aware of any hole that is likely to get
plugged by bundling an additional library.


There still seem to be plenty of holes left. (No standard Finite
Element Analysis or Digital Signal Processing libs for example.)

Or put another way, what is so important about the holes that are filled
by packages like GLUT,HGL,OpenGL,html,parsec,pretty,xhtml (to name a
few) that require standard library implementations.


Should
something experimental be a base package? And shouldn't all modules that are
base packages declare their status?


No, they should all be reasonably stable. Things that are unstable are
likely to move out of the standard libraries and just become hackage
packages.


Libs are not standard simply because they happen to be bundled with
ghc. And how is it that such unstable libs came to be bundled in the
first place, given the alleged superior stability and quality control

:-)

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


[Haskell-cafe] Re: Building production stable software in Haskell

2007-09-18 Thread Simon Marlow

Adrian Hey wrote:

Neil Mitchell wrote:

Hi


They are less stable and have less quality control.

Surely you jest? I see no evidence of this, rather the contrary in fact.


No, dead serious. The libraries have a library submission process.


It does not follow that libraries that have not been submitted
to this process are less stable and have less quality control. Nor
does it follow that libraries that have been through this submission
process are high quality, accurately documented, bug free and efficient
(at least not ones I've looked at and sometimes even used).


Adrian's right - the set of libraries that are shipped with GHC is 
essentially random.  A bit of history:


Originally we shipped pretty much all freely-available non-trivial Haskell 
libraries with GHC.  At some point (about 5 years ago or so) the number of 
Haskell libraries started to grow beyond what we could reasonably ship with 
GHC, and some of them were providing duplicate functionality, so we stopped 
adding to the set.  We made a few small exceptions (e.g. filepath) for 
things that we felt really should be in the default GHC install, but to a 
large extent the set of libraries that are shipped with GHC has remained 
constant over the last 3 major releases.


In 6.6, we made a nomenclature change: we divided the packages shipped 
with GHC into two: those that are required to bootstrap GHC (the boot 
libraries, until recently called the core libraries), and the others that 
we just include with a defualt binary install (the extra libraries).  On 
some OSs, e.g. Debian, Ubuntu, Gentoo, you don't even get the extra 
libraries by default.  This was intended to be a stepping stone to 
decoupling GHC from these libraries entirely, which is possible now that we 
have Cabal and Hackage.


What I'm getting around to is that being shipped with GHC is not a 
category that has any particular meaning right now.  I think it's time the 
community started to look at what libraries we have in Hackage, and 
identify a subset that we should consider standard in some sense - that 
is, those to which the library submission process applies, at the least. 
If there were such a set, we could easily make GHC's extra libraries 
equal to it.


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


Re: [Haskell-cafe] Library Process (was Building production stable software in Haskell)

2007-09-18 Thread Ketil Malde
On Tue, 2007-09-18 at 11:14 +0100, Malcolm Wallace wrote:

 I would like to see the same separation forming between the ghc compiler
 itself (which would minimally include only the small number of libraries
 needed to build the compiler), and larger distributions which would be
 maintained by other people, and include much larger collections of
 packages that the maintainer has tested and verified to work together.

I think there is a niche for a subset of the hackage libraries providing
an officially sanctioned standard library collection.  Currently,
hackage includes, well, everything.  As such, it is a useful resource,
but it would be useful to have a partitioning into two levels, where the
SLC would only include libraries that meet specific criteria.  Maybe:

 - considered stable
 - is portable
 - relies only on other standard libraries
 - avoids needless duplication of functionality
 - with a responsive, named maintainer (not libraries@)
 - with acceptable documentation and unit tests
 - required by at least one separate application

-k


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


Re: [Haskell-cafe] Library Process (was Building production stable software in Haskell)

2007-09-18 Thread Neil Mitchell
Hi

 I think there is a niche for a subset of the hackage libraries providing
 an officially sanctioned standard library collection.  Currently,
 hackage includes, well, everything.  As such, it is a useful resource,
 but it would be useful to have a partitioning into two levels, where the
 SLC would only include libraries that meet specific criteria.  Maybe:

  - considered stable
  - is portable
  - relies only on other standard libraries
  - avoids needless duplication of functionality
  - with a responsive, named maintainer (not libraries@)
  - with acceptable documentation and unit tests
  - required by at least one separate application

I think there is a niche for this, but I don't think it should be an
officially sanctioned collection - since otherwise everyone is just
going to be debating how to add their library to this collection - and
we are going to descend into voting and politics. Instead, I think
several people should make their own personal list of libraries they
would vouch for - which meet the criteria above AND they have
personal positive experiences of.

Off the top of my head my list would include gtk2hs, and that's about it.

Thanks

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


Re: [Haskell-cafe] How can I stop GHCi from calling show for IOactions?

2007-09-18 Thread Claus Reinke

| It seems that GHCi outputs the contents of the variable you've created
| when there's only one of them.

Indeed, that is documented behaviour (first bullet here:
http://www.haskell.org/ghc/docs/latest/html/users_guide/ch03s04.html#ghci-stmts
)
Perhaps it's confusing behaviour?  If so do suggest an alternative.


why not simply do what the flag suggests, either always try to
print the bind-result, or never? i assume there has been a use
case where this special case has been found useful/necessary?

as for earlier questions/suggestions in this thread:


 Is there a way to make GHCi not print the result
of an action but still make my variables get bound?


This seems to be a common question (I myself asked it recently), so
I've added an entry to the GHCi page on the wiki.

Ideally, it would be nice if this were discoverable from within GHCi,
but I'm not sure how this would best be done.


i've run into this myself!-) there is a patch pending for ghc head 
(so it may not be in 6.8.1:-( that would show the GHCi-specific 
flags together with the GHCi options:


   Prelude :set
   options currently set: none.
   GHCi-specific dynamic flag settings:
 -fno-print-explicit-foralls
 -fprint-bind-result
 -fno-break-on-exception
 -fno-break-on-error
 -fno-print-evld-with-show
   other dynamic, non-language, flag settings:
   ..

so you'd at least know which possibly relevant flags there
are, and if the names are not expressive enough, the :help would
point you to the flag reference:

   :help
   ..
 Options for ':set' and ':unset':
   
   +rrevert top-level expressions after each evaluation

   +sprint timing/memory stats after each evaluation
   +tprint type after evaluation
   -flags  most GHC command line flags can also be set here
(eg. -v2, -fglasgow-exts, etc.)
   for GHCi-specific flags, see User's Guide,
   Flag reference, Interactive-mode options
   ..


I've always wondered if ghc(i) --help should be a bit more
instructive, or perhaps if there were a man page that lay somewhere
between the --help message and the manual in terms of
comprehensiveness. It's a pretty major jump from a short description
of 4 command line options (only one of which I have ever used) to the
entire manual, with a ~10 page table of contents.


please note that the flag reference, which was pointed to 
earlier in this thread, is just such a summary, and there's

a subsection dedicated to GHCi-specific options. there
isn't much in that section in 6.6.1:

http://www.haskell.org/ghc/docs/latest/html/users_guide/flag-reference.html#id3132588

but in ghc head and the upcoming 6.8, you'll find most of 
the GHCi-related flags summarized there.


hth,
claus

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


Re: [Haskell-cafe] Library Process (was Building productionstable software in Haskell)

2007-09-18 Thread Claus Reinke

I thought the master plan was that less would come with the compiler /
interpreter and the user would install packages using cabal.


Ideally, yes.  I think a useful model would be GNU/Linux, where there is
the Linux kernel, developed by core hackers, and then there are
distributions, which package up particular kernels with a load of
different GNU libraries and utilities to form a complete operating
environment.  The maintainers of the distributions do not work on the
kernel, but they do test their own combinations of kernel/libraries +
utilities to ensure that everything plays together nicely.

I would like to see the same separation forming between the ghc compiler
itself (which would minimally include only the small number of libraries
needed to build the compiler), and larger distributions which would be
maintained by other people, and include much larger collections of
packages that the maintainer has tested and verified to work together.
In the best of all worlds, a Haskell distribution would include
multiple compilers, not just ghc.


i think that such separately maintained distributions would be 
one way to avoid the version skew chaos that might otherwise 
result from dropping all but the minimal set of libraries from 
ghc/hugs/.. distributions. now everybody take a step back to 
make room for the volunteers?-)


a slightly more lightweight approach, that could grow into the
above, would be if cabal packages supported nesting/grouping, 
so that sets of useful/proven libs could be bundled into a single 
package (the whole package builds if all the subpackages build 
individually, and form a coherent whole; that is, there'd need to 
be tests checking that the subpackages are actually compatible 
versions).


then, instead of extra-libs in ghc/hugs/.., there'd be a 
standard-libs package on hackage showing exactly which 
haskell implementations it buildstests with successfully and 
which not. and one could still get a whole consistent and 
maintained? bunch of standard libs in one go.

/dream

claus

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


Re: [Haskell-cafe] unique id for data types

2007-09-18 Thread Neil Mitchell
Hi Barney,

This may be of interest, since all types already have an Int
associated with them:

http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Typeable.html#v%3AtypeRepKey

Thanks

Neil


On 9/18/07, Barney Hilken [EMAIL PROTECTED] wrote:
 In order to make my records system practically useable, I need a type
 family

type family NameCmp n m

 which totally orders datatypes. More precisely, it should return one
 of the
 following types:

data NameLT = NameLT
data NameEQ = NameEQ
data NameGT = NameGT

 for each pair of datatypes n  m, according to whether n  m, n = m,
 or n  m
 in some global ordering. This ordering needs to be independent of the
 context,
 so it can't be affected by whatever imports there are in the current
 module.

 What I want to know is: does GHC give datatypes any global id I could
 use to
 generate such an ordering? Would fully qualified names work?

 Secondly (assuming it's possible) how easy would it be for me to
 write a patch
 to add NameCmp to GHC? Where in the source should I start looking?

 Thanks,

 Barney.


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

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


Re: [Haskell-cafe] Re: Building production stable software in Haskell

2007-09-18 Thread Arthur van Leeuwen


On 18-sep-2007, at 14:10, Simon Marlow wrote:


Adrian Hey wrote:

Neil Mitchell wrote:

Hi


They are less stable and have less quality control.
Surely you jest? I see no evidence of this, rather the contrary  
in fact.


No, dead serious. The libraries have a library submission process.

It does not follow that libraries that have not been submitted
to this process are less stable and have less quality control. Nor
does it follow that libraries that have been through this submission
process are high quality, accurately documented, bug free and  
efficient

(at least not ones I've looked at and sometimes even used).


Adrian's right - the set of libraries that are shipped with GHC is  
essentially random.  A bit of history:


Originally we shipped pretty much all freely-available non-trivial  
Haskell libraries with GHC.  At some point (about 5 years ago or  
so) the number of Haskell libraries started to grow beyond what we  
could reasonably ship with GHC, and some of them were providing  
duplicate functionality, so we stopped adding to the set.  We made  
a few small exceptions (e.g. filepath) for things that we felt  
really should be in the default GHC install, but to a large extent  
the set of libraries that are shipped with GHC has remained  
constant over the last 3 major releases.


In 6.6, we made a nomenclature change: we divided the packages  
shipped with GHC into two: those that are required to bootstrap  
GHC (the boot libraries, until recently called the core  
libraries), and the others that we just include with a defualt  
binary install (the extra libraries).  On some OSs, e.g. Debian,  
Ubuntu, Gentoo, you don't even get the extra libraries by  
default.  This was intended to be a stepping stone to decoupling  
GHC from these libraries entirely, which is possible now that we  
have Cabal and Hackage.


What I'm getting around to is that being shipped with GHC is not  
a category that has any particular meaning right now.  I think it's  
time the community started to look at what libraries we have in  
Hackage, and identify a subset that we should consider standard  
in some sense - that is, those to which the library submission  
process applies, at the least. If there were such a set, we could  
easily make GHC's extra libraries equal to it.


Ofcourse, now we hit the situation that Eclipse is in as well:
everything worthwhile should be downloaded next to the base
functionality. This has lead to many slightly differing distributions
of Eclipse. The same problem occurs with Linux distributions...

I personally always liked Python's 'batteries included' approach.
Python comes with enough libs standard to be genuinely useful.
This, I think, is a good model from a marketing point of view.

With regards, Arthur.

--

  /\/ |   [EMAIL PROTECTED]   | Work like you don't need  
the money
/__\  /  | A friend is someone with whom | Love like you have never  
been hurt
/\/__ | you can dare to be yourself   | Dance like there's nobody  
watching




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


Re: [Haskell-cafe] unique id for data types

2007-09-18 Thread Barney Hilken

Hi Neil, thanks for the response.

The problem is this:
It is in the IO monad because the actual value of the key may vary  
from run to run of the program
(taken from the web page). Since I'm relying on the order, not just  
equality, this will seriously

screw things up, because my records are done at compile time.


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


[Haskell-cafe] Re: [Haskell] Blocked STM GC question

2007-09-18 Thread Jules Bean

Simon Marlow wrote:

Ashley Yakeley wrote:
If I have a thread that's blocked on an STM retry or TChan read, and 
none of its TVars are referenced elsewhere, will it get stopped and 
garbage-collected?


I have in mind a pump thread that eternally reads off a TChan and 
pushes the result to some function. If the TChan is forgotten 
elsewhere, will the permanently blocked thread still sit around using 
up some small amount of memory, or will it be reaped by the garbage 
collector?


In this case, your thread should receive the BlockedIndefinitely exception:

http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Exception.html#v%3ABlockedIndefinitely 



If the system is idle for a certain amount of time (default 0.3s, change 
it with the +RTS -I option) a full GC is triggered, which will detect 
any threads that are blocked on unreachable objects, and arrange to send 
them the BlockedIndefinitely exception.



Including MVars? Your quoted text suggests 'Yes' but the docs you link 
to suggest 'No'.


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


[Haskell-cafe] Re: [Haskell] Blocked STM GC question

2007-09-18 Thread Simon Marlow

Jules Bean wrote:

Simon Marlow wrote:

Ashley Yakeley wrote:
If I have a thread that's blocked on an STM retry or TChan read, and 
none of its TVars are referenced elsewhere, will it get stopped and 
garbage-collected?


I have in mind a pump thread that eternally reads off a TChan and 
pushes the result to some function. If the TChan is forgotten 
elsewhere, will the permanently blocked thread still sit around using 
up some small amount of memory, or will it be reaped by the garbage 
collector?


In this case, your thread should receive the BlockedIndefinitely 
exception:


http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Exception.html#v%3ABlockedIndefinitely 



If the system is idle for a certain amount of time (default 0.3s, 
change it with the +RTS -I option) a full GC is triggered, which will 
detect any threads that are blocked on unreachable objects, and 
arrange to send them the BlockedIndefinitely exception.



Including MVars? Your quoted text suggests 'Yes' but the docs you link 
to suggest 'No'.


Deadlocked threads blocked on MVars instead get the BlockedOnDeadMVar 
exception.  Perhaps those two exceptions should be merged.


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


[Haskell-cafe] Re: [Haskell] Swapping parameters and type classes

2007-09-18 Thread Simon Marlow

Ian Lynagh wrote:

On Tue, Sep 18, 2007 at 03:48:06PM +0100, Andrzej Jaworski wrote:

Responding to Simon Peyton-Jones'  reminder that this is a low-bandwidth list I
was obscure and commited a blunder.

This one and many other threads here are started undoubtedly by experts [sorry
guys:-)] and coffee brake should work for them, but on numerous occasions
threads here spawn beginner type questions. So, my thinking was that it is
perhaps against the tide trying to stop them.
Why not to make the list Haskell a first contact general practitioner? Then
creating e.g. Announcements  Challenge or Announcements  ask guru list
could take the best from Haskell but also would make it less front line and
thus more elitist, which should imply the manner by itself.


I proposed renaming
haskell@ - haskell-announce@
haskell-cafe@ - haskell@
in http://www.haskell.org/pipermail/haskell-cafe/2007-July/028719.html


I suggested the same thing at the time we created haskell-cafe, but the 
concensus was in favour of haskell-cafe.  At the time I didn't think it 
would work - for a long time, the number of subscribers to both lists was 
almost the same - but now I have to admit I think haskell-cafe is a big win 
for the community.  The -cafe extension gives people the confidence to post 
any old chatter without fear of being off-topic, and I'm sure this has 
helped the community to grow.


Those of us who grew up with Usenet (RIP) are more at home with the 
foo/foo-announce split, and it's certainly quite conventional for 
mailing-list naming too, but on the whole I don't think doing things 
differently has really done us any harm and it may well have been a stroke 
of genius :-)


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


[Haskell-cafe] transparent parallelization

2007-09-18 Thread Thomas Girod
Hi there. Beeing rather new to the realm of Haskell and functional
programming, I've been reading about how is easier it is to parallelize
code in a purely functional language (am I right saying that ?).

My knowledge of parallelization is also very weak, but I've been thinking
about this and I have a question. Let's say we take a small piece of code,
like the quicksort algorithm.

 qsort [] = []
 qsort (x:xs) = qsort lesser ++ [x] ++ qsort greater
 where lesser = filter (x) xs
   greater = filter (=x) xs

(actually I didn't test this code, this is just for the example)

Here, computing lesser and greater are two disjoint actions - we don't
need the result from one to compute the other, and haskell does not allow
one to alter data so that would change the behaviour of the other. So I
guess those could be run in parallel.

Would it be fairly simple to automatically determine parts of code that can
be run in parallel, and parts that cannot (at least in non-monadic code) ?

So the final question is : if it is possible to automatically define
segments of code that can be run in parallel, is [insert compiler name here]
compiling this code as a one thread thing, or as a multithreaded version ?

I guess on single processor machines, it is more efficient to do it as a
single thread - but with those many-cores processors that are coming, it
probably won't be true anymore.

Sorry if this post is blowing off open doors (I guess this doesn't mean
anything in english but it sounds cool) ...

Regards

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


Re: [Haskell-cafe] Re: Type-Marking finite/infinte lists?

2007-09-18 Thread Bas van Dijk
On 9/18/07, apfelmus [EMAIL PROTECTED] wrote:
 ...in reality, foldr is (almost) the induction principle for natural numbers!

Oh yes, nice observation!

Afpelmus, thanks for your thorough answers!

regards,

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


Re: [Haskell-cafe] Building production stable software in Haskell

2007-09-18 Thread brad clawsie
On Mon, Sep 17, 2007 at 05:26:05PM +0100, Neil Mitchell wrote:
 Compare me changing my tagsoup library, to me changing my filepath
 library which comes bundled with GHC. I can do anything I want to the
 tagsoup library, but I need to wait at least 2 weeks and get general
 consensus before changing filepath.

okay, but this fails in some cases. i wrote a package to obtain
financial quotes. yahoo changed the webservice url on me. i rolled out
a change within a day. in your model, people suffer a broken service
for two weeks.

clearly there is a time and a place for code review. there is also a
time and a place for rapid response.
 
 Also some libraries on hackage are 0.1 etc - even the author doesn't
 particularly think they are stable!

this is a sound practice and i applaud the authors for safely and
soundly warning potential users of code immaturity. when my code has
been in use for a year or so with no error reports, then i will say
that it is stable and give it a 1.0 designation. until then, it is 
indeed in a testing mode.

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


Re: [Haskell-cafe] Building production stable software in Haskell

2007-09-18 Thread Neil Mitchell
Hi

 okay, but this fails in some cases. i wrote a package to obtain
 financial quotes. yahoo changed the webservice url on me. i rolled out
 a change within a day. in your model, people suffer a broken service
 for two weeks.

I don't think Yahoo will change the syntax or semantics of filepaths
anytime soon :-)

If a new operating system (say Vista) had changed the semantics of
filepaths then that would have been a fix, not a change, and provided
it doesn't alter the behaviour for others then that would have been a
bug fix that went in immediately. The code review is for interfaces -
internal details are a bit more free, and clear bug fixes are not
voted upon.

Thanks

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


[Haskell-cafe] Re: [Haskell] Swapping parameters and type classes

2007-09-18 Thread Andrzej Jaworski
Salute Simon, hi everybody here!

Ian is scientific in his observations and has a valid point. I share his
objection to the Haskell list as unnecessarily misleading newcomers which, I
would add, sets precedents for others to be verbose. Then, creating a Beginner
list is less fortunate than creating Announcements list for obvious and not so
obvious reasons. There are things in this culture however that make the decision
difficoult. What stands out is that announcements gained in the Haskell list
much wider connotation and by renaming it into this name explicitly might kill
this overinterpretation and thus couple of interesting oservations might not
find its way to an audience. Ian's numbers tell however that this benefits
speakers more than the listeners;-)

Haskell-Cafe though deserves respect on the same scienific ground - the share
volume speeks for it!
I agree with you Simon that the name Cafe created sort of spiritual component to
the community which should not be underestimated. We are humans and even history
of mathematics is a stream of fashion between couple of great discoveries.

Cheers,
-Andrzej

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


Re: [Haskell-cafe] yi-gtk

2007-09-18 Thread Andrea Rossato
On Tue, Sep 18, 2007 at 09:20:44AM +0800, clisper wrote:
 who knows how to compile yi-gtk?
 i tried,but it told me mine  miss gtk.

probably what you need is gtk2hs:
http://haskell.org/gtk2hs/

andrea

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


Re: [Haskell-cafe] Building production stable software in Haskell

2007-09-18 Thread Don Stewart
hughperkins:
 Just out of curiosity, how could one do something like a factory, so
 that by default a library uses, say, Data.Map, but by making a simple
 assignment we can switch the library to use a different
 implementation?

Polymorphism, specifically, typeclasses, would be one option here.

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


Re: [Haskell-cafe] Library Process (was Building production stable software in Haskell)

2007-09-18 Thread Thomas Hartman
  Instead, I think
several people should make their own personal list of libraries they
would vouch for 

Ideally along with a cabal (or otherwise) install script that would set 
everything up in one step.




Neil Mitchell [EMAIL PROTECTED] 
Sent by: [EMAIL PROTECTED]
09/18/2007 09:02 AM

To
Ketil Malde [EMAIL PROTECTED]
cc
haskell-cafe@haskell.org, Malcolm Wallace [EMAIL PROTECTED]
Subject
Re: [Haskell-cafe] Library Process (was Building production stable 
software in Haskell)






Hi

 I think there is a niche for a subset of the hackage libraries providing
 an officially sanctioned standard library collection.  Currently,
 hackage includes, well, everything.  As such, it is a useful resource,
 but it would be useful to have a partitioning into two levels, where the
 SLC would only include libraries that meet specific criteria.  Maybe:

  - considered stable
  - is portable
  - relies only on other standard libraries
  - avoids needless duplication of functionality
  - with a responsive, named maintainer (not libraries@)
  - with acceptable documentation and unit tests
  - required by at least one separate application

I think there is a niche for this, but I don't think it should be an
officially sanctioned collection - since otherwise everyone is just
going to be debating how to add their library to this collection - and
we are going to descend into voting and politics. Instead, I think
several people should make their own personal list of libraries they
would vouch for - which meet the criteria above AND they have
personal positive experiences of.

Off the top of my head my list would include gtk2hs, and that's about it.

Thanks

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



---

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


Re: [Haskell-cafe] Library Process (was Building production stable software in Haskell)

2007-09-18 Thread Sven Panne
On Tuesday 18 September 2007 09:44, Dominic Steinitz wrote:
 This discussion has sparked a question in my mind:

 What is the process for the inclusion of modules / packages in ghc, hugs
 and other compilers  interpreters?

Personal interest of the people working on GHC et. al. ;-)

 I thought the master plan was that less would come with the compiler /
 interpreter and the user would install packages using cabal. [...]

Although this statement might be a bit heretical on this list, I'll have to 
repeat myself again that Cabal, cabal-install, cabal-whatever will *never* be 
the right tool for the end user to install Haskell packages on platforms with 
their own packaging systems like RPM (the same holds for other systems, I 
just use RPM as an example here). This packaging system, and nothing else, 
will write into my /usr, otherwise chaos and versioning hell will threaten 
the system integrity. Cabal is a very fine tool to be used from RPM .spec 
files and to develop below one's own home directory, but it is not the tool 
of choice for the final installation. There are various reasons for this:

   * Imagine you want to find out to which package in which version a given 
file belongs. Impossible, if RPM is bypassed.

   * RPM offers functionality to verify the integrity of the installed SW, it 
can tell me which files are documentation, which ones are configuration 
files, etc. All this meta information has to be in a single system.

   * YaST, yum, etc. already have the notion of repositories, trust (via 
standard cryptographic methods) and resolving transitive dependencies, so we 
would re-implement things which are already there, well maintained and 
well-known to end users.

   * Imagine every language would force their end users to use specific tools 
for installation, this would be ridiculous. Personally I don't care at all 
about the details how Perl modules, some PHP/Python/... libraries etc. are 
installed on my system. This knowledge belongs to the packager who builds a 
nice RPM, mentioning all dependencies, so my favourite RPM tool can 
transitively resolve, download and install everything, offering a nice GUI if 
I like. No need to remember how to do this for Perl/PHP/Python/etc.

Regarding the pros and cons of small, separate packages: In general I agree 
that this is the right direction, and this is what other languages do as 
well. There are e.g. tons of Perl/PHP/Python/Ruby RPMs available for my 
system, each offering a specific library, while the RPMs containing the 
interpreters/compilers are rather small. But: IMHO we are not there yet, 
because we still have to remove quite a few rough edges until we can smoothly 
offer e.g. an RPM repository with lots of small library RPMs (Cabal 
versionitis, updating the Haddock documentation index, etc.). Therefore, I'll 
continue to offer only Sumo-style RPMs for GHC + boot-libs + extra-libs for 
now, but I hope I can change this in the future.

Another point: Although this is hard to believe nowadays, ;-) people are not 
always online, so simply installing what is missing might not always be an 
option. Great, I'd really need the foobar-2.1 package now, but I'm currently 
1 feet above the Atlantic ocean... The right way to tackle this problem 
is using meta packages, basically referencing lots of bundled small packages. 
RPM offers such a feature, and I guess other systems, too. On a laptop, such 
a meta package leading to the installation of tons of libraries is the right 
approach, on a fixed workstation the story might be different.

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


Re: [Haskell-cafe] transparent parallelization

2007-09-18 Thread Thomas Schilling
On Tue, 2007-09-18 at 18:13 +0200, Thomas Girod wrote:
 Hi there. Beeing rather new to the realm of Haskell and functional
 programming, I've been reading about how is easier it is to
 parallelize code in a purely functional language (am I right saying
 that ?).
 
 My knowledge of parallelization is also very weak, but I've been
 thinking about this and I have a question. Let's say we take a small
 piece of code, like the quicksort algorithm.
 
  qsort [] = []
  qsort (x:xs) = qsort lesser ++ [x] ++ qsort greater 
  where lesser = filter (x) xs
greater = filter (=x) xs
 
 (actually I didn't test this code, this is just for the example)
 
 Here, computing lesser and greater are two disjoint actions - we
 don't need the result from one to compute the other, and haskell does
 not allow one to alter data so that would change the behaviour of the
 other. So I guess those could be run in parallel. 
 
 Would it be fairly simple to automatically determine parts of code
 that can be run in parallel, and parts that cannot (at least in
 non-monadic code) ?
 
 So the final question is : if it is possible to automatically define
 segments of code that can be run in parallel, is [insert compiler name
 here] compiling this code as a one thread thing, or as a multithreaded
 version ? 
 
 I guess on single processor machines, it is more efficient to do it as
 a single thread - but with those many-cores processors that are
 coming, it probably won't be true anymore.
 
 Sorry if this post is blowing off open doors (I guess this doesn't
 mean anything in english but it sounds cool) ... 
 

Detecting parallelism is possible, but generally rather fragile.
Coarse-grained parallelism in form of threads (or processes) is only
efficient if enough data can be processed in parallel.  This in turn is
determined by the data-dependencies, which are hard to detect
automatically.  To preserve program semantics the analysis has to be
conservative, i.e., assume that two parts of a program depend on each
other unless it can prove otherwise.  (OpenMP relies on the programmer
to explicitly declare what to parallelize.)

A better way is to let the user specify the algorithm at a higher level.
One very promising technique to do this is explored in Data Parallel
Haskell (DPH) [1].  In DPH you specify your algorithm as functional
programs operating on vectors, and even allows nested parallelism, i.e.,
you can call parallel functions inside parallel functions.  If
implemented naïvely, this could easily lead to inefficiencies due to too
little workload per thread.  This is where GHCs rewriting capabilities
kick in and transform nested parallel programs into flat parallel
programs.  I really recommend reading the paper(s) (see [1]).

/ Thomas

[1] .. http://haskell.org/haskellwiki/GHC/Data_Parallel_Haskell


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


Re: [Haskell-cafe] Library Process (was Building production stable software in Haskell)

2007-09-18 Thread brad clawsie
On Tue, Sep 18, 2007 at 07:24:08PM +0200, Sven Panne wrote:
 Although this statement might be a bit heretical on this list, I'll have to 
 repeat myself again that Cabal, cabal-install, cabal-whatever 
 will *never* be the right tool for the end user to install Haskell 
 packages on platforms with their own packaging systems like RPM   

this is a valid point. personally i only install cabal packages as
--user and most tool-specific package managers (cpan etc) tend to
offer this as an option. 

cabal is still necessary. it fills the gap where most OS package
platforms won't provide support. even on the most supported platform
(.deb for debian and ubuntu i presume), you still likely only get
about 20% of what is in hackage on your system. what about everything
else? i would prefer to have cabal in place of make install.

the only plausible solution i can see is generated OS packages
(i.e. hackage hosts .deb, .rpm, and bsd packages on its own). this is
likely the only realistic approach, but also periodically creates
breakage too, particularly if the OS one day creates its own blessed
packages.

i would be willing to look into auto-generating freebsd packages,
might be a fun project.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] transparent parallelization

2007-09-18 Thread bf3
 http://haskell.org/haskellwiki/GHC/Data_Parallel_Haskell

Wow this is cool stuff! It would be nice to have something like this for the 
Playstation 3 :-)

Regarding parallelism, I wander how this extension will compare to Sun's 
Fortress language, if/when it gets finally released.

Peter


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


Re: [Haskell-cafe] transparent parallelization

2007-09-18 Thread Dave Tapley
If I recall correctly a rather neat way of exploiting this property of
qsort is exploited with Nested Data Parallelism and covered in this
talk:
http://www.londonhug.net/2007/05/25/video-of-spjs-talk-is-now-online/

Good food for thought :)

Dave,

On 18/09/2007, Thomas Girod [EMAIL PROTECTED] wrote:
 Hi there. Beeing rather new to the realm of Haskell and functional
 programming, I've been reading about how is easier it is to parallelize
 code in a purely functional language (am I right saying that ?).

 My knowledge of parallelization is also very weak, but I've been thinking
 about this and I have a question. Let's say we take a small piece of code,
 like the quicksort algorithm.

  qsort [] = []
  qsort (x:xs) = qsort lesser ++ [x] ++ qsort greater
  where lesser = filter (x) xs
greater = filter (=x) xs

 (actually I didn't test this code, this is just for the example)

 Here, computing lesser and greater are two disjoint actions - we don't
 need the result from one to compute the other, and haskell does not allow
 one to alter data so that would change the behaviour of the other. So I
 guess those could be run in parallel.

 Would it be fairly simple to automatically determine parts of code that can
 be run in parallel, and parts that cannot (at least in non-monadic code) ?

 So the final question is : if it is possible to automatically define
 segments of code that can be run in parallel, is [insert compiler name here]
 compiling this code as a one thread thing, or as a multithreaded version ?

 I guess on single processor machines, it is more efficient to do it as a
 single thread - but with those many-cores processors that are coming, it
 probably won't be true anymore.

 Sorry if this post is blowing off open doors (I guess this doesn't mean
 anything in english but it sounds cool) ...

 Regards

 Thomas Girod



 ___
 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] transparent parallelization

2007-09-18 Thread Jan-Willem Maessen


On Sep 18, 2007, at 4:24 PM, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:


http://haskell.org/haskellwiki/GHC/Data_Parallel_Haskell


Wow this is cool stuff! It would be nice to have something like  
this for the Playstation 3 :-)


Regarding parallelism, I wander how this extension will compare to  
Sun's Fortress language, if/when it gets finally released.


The scope of the two is very different.  DPH proposes a single rather  
flexible data structure---nested Data Parallel Arrays (really as much  
list-like as array-like).  The underlying data structure is  
manipulated using bulk operations like zip, sum, and comprehensions.


By contrast, Fortress defines the notion of a Generator which you  
can think of as being akin to a parallel version of Data.Traversable  
or ListLike, where the fundamental primitive is a generalization of  
foldP and mapP.  This is strictly more general---we can define many  
of the operations in Data.PArr on arbitrary data types, permitting us  
to talk about the sum of the elements of a set, or mapping a function  
across a distributed array.  We can define nested data parallel  
arrays in Fortress.  There isn't (yet) an equivalent of the RULES  
pragma that permits Fortress to optimize combinations of function  
calls.  However, clever uses of type information and function  
overloading let Fortress do some interesting program transformations  
of its own (eg early exit for reductions with left zeros).  Finally,  
Fortress actually has a mechanism for defining new types of  
comprehensions (though this isn't in the language specification yet).
The other nice thing about Generators is that we can support  
consumption of large or infinite things, if we're very careful about  
how we do the consumption.  We're planning to write the equivalent of  
hGetContents that works over blocks of file data in parallel where  
possible, but processes streams as chunks of data become available.   
It remains to be seen how this will work out in practice, though.   
Our goal is something LazyByteString or rope-like.



So: DPH: available today (-ish), one (very flexible) data structure.   
Bulk operations on a data structure run in parallel.  Relies on RULES  
+ special compiler support (am I getting that right?  You can fuse  
multiple traversals of a common argument, which isn't doable using  
RULES, right?) to make it all run nicely.  A well-established  
performance model, cribbed from NESL, for the PArr bits.


Fortress: Arrays and lists currently built in.  Bulk operations on a  
data structure can run in parallel.  Ability to define new parallel  
types with carefully-tailored traversal (eg we have a PureList that's  
based on Ralf Hinze and Ross Paterson's finger tree where traversal  
walks the tree structure in parallel).  No optimization RULES yet (an  
interpreter doesn't optimize), but a good deal of type-based code  
selection.  Implementation less complete than DPH in general (even  
the Generator API is in flux, though the fundamental use of a foldP- 
like operation hasn't changed over time).


-Jan-Willem Maessen
 Longtime Haskell Hacker
 Fortress Library Developer

PS - By the way, working on Generators has increased my suspicion  
that comprehensions do NOT have a naturally monadic structure (which  
bugged me when I worked on parallel list traversal optimization in pH  
back in 1994).  It just happens that for cons-lists the two  
structures happen to coincide.  If anyone else has had similarly  
subversive thoughts I'd love to chat.

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


Re: [Haskell-cafe] transparent parallelization

2007-09-18 Thread Derek Elkins
On Tue, 2007-09-18 at 18:13 +0200, Thomas Girod wrote:
 Hi there. Beeing rather new to the realm of Haskell and functional
 programming, I've been reading about how is easier it is to
 parallelize code in a purely functional language (am I right saying
 that ?).
 
 My knowledge of parallelization is also very weak, but I've been
 thinking about this and I have a question. Let's say we take a small
 piece of code, like the quicksort algorithm.
 
  qsort [] = []
  qsort (x:xs) = qsort lesser ++ [x] ++ qsort greater 
  where lesser = filter (x) xs
greater = filter (=x) xs
 
 (actually I didn't test this code, this is just for the example)
 
 Here, computing lesser and greater are two disjoint actions - we
 don't need the result from one to compute the other, and haskell does
 not allow one to alter data so that would change the behaviour of the
 other. So I guess those could be run in parallel. 
 
 Would it be fairly simple to automatically determine parts of code
 that can be run in parallel, and parts that cannot (at least in
 non-monadic code) ?

The problem with Haskell is not finding opportunities to parallelize,
they are legion. Actually, quite the opposite, there's so much that your
code ends up slower than a sequential realization.  The hard part is
making a good cost-model and a good way to create coarser chunks of
work.  It's not worthwhile to spawn a thread (even a very lightweight
one) for virtually every subexpression.

Automatic parallelization is easy, efficient parallelization is hard.

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


[Haskell-cafe] ANN: hstats-0.1

2007-09-18 Thread Marshall Beddoe
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/hstats-0.1

I've just released hstats, a statistical computing module for the Haskell
language.  Current functionality includes: mean, median, mode, range,
standard/average deviation, variance, iqr, kurtosis, skew, covariance, and
correlation. I have plans on adding more rank correlation functions,
histograms  chi square tests.

darcs repo: http://www.sftank.net/code/hstats
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Missing Symbol

2007-09-18 Thread PR Stanley

Hi
What symbol would you replace the ? with:
the identity function
id x = x?
My scanned copy of the Hutton book contains some rather interesting 
characters. In fact, the OCR program has placed a . in place of 
most symbols - e.g. -, - ^, =, \=, etc.
Fortunately, I'm able to guess the correct operator in the majority 
of the cases.

Cheers, Paul

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


Re: [Haskell-cafe] Missing Symbol

2007-09-18 Thread PR Stanley



 Hi
 What symbol would you replace the ? with:
 the identity function
 id x = x?

I don't think I'd have anything where the ? symbol is.

id x = x works just fine.
Ah, that's interesting because there's a . to the right of 
x in my scanned doc. Still, if no symbol is necessary, so much the better!

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