Re: [Haskell-cafe] parsec and bytestring; was: hxt memory useage

2008-01-25 Thread Johan Tibell
On Jan 24, 2008 10:34 PM, Matthew Pocock [EMAIL PROTECTED] wrote:
 Would a bytestring-backed implementation of parsec solve my problems? Is there
 such a beast out there?

I'm working on one as a part of another project. It's not incremental
and needs some optimizing (I've focused on correctness so far.) I
don't think it solves your problem though as you'll only save a
constant amount of memory by using ByteStrings over Strings and it may
not be enough. I also don't know how to integrate it with HXT. In case
you want to have a look anyway you can find it here:

http://darcs.johantibell.com/hyena/Hyena/ByteStringParser.hs

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


[Haskell-cafe] Fwd: ByteString Parsec clone

2008-01-25 Thread Johan Tibell
I tried to get Dan's thoughts on cloning parts of the Parsec interface
and some of the documentation but none of the emails addresses I've
tried seem to work. What's allowed when it comes to duplicating
something like an API? What about the documentation? I intend it to be
released under BSD3 which I believe is used for Parsec as well.

Anyone know how I can reach Dan?

-- Johan

-- Forwarded message --
From: Johan Tibell [EMAIL PROTECTED]
Date: Jan 22, 2008 2:56 PM
Subject: ByteString Parsec clone
To: [EMAIL PROTECTED]


I've written, but yet not published, a ByteString version of parts of
the Parsec API as a part of a web application server project. I've
currently used almost the exact wording from your documentation (as
the semantics of the functions is intended to be the same as in
Parsec.) Are you OK with that?

P.S. I intend to give my library a different name as it has different
module structure and doesn't support a lot of Parsec's features. It
will be BSD licensed.

Best regards,

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


Re: [Haskell-cafe] Re: cryptographic hash functions in darcs (re: announcing darcs 2.0.0pre3)

2008-01-25 Thread Lutz Donnerhacke
* zooko wrote:
 This makes the choice of SHA-1 for the patch-id-generation function  
 wholly inappropriate.  We already know that SHA-1 doesn't have  
 collision resistance, and there is reason to suspect that in the near  
 future it will turn out that it doesn't have second-pre-image  
 resistance either.

Calm down! The found collisions in SHA-1 require some very specific
environment choices. I doubt darcs will allow those preconditions.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Why functional programming matters

2008-01-25 Thread ChrisK

Simon Peyton-Jones wrote:

1. Small examples of actual code.


I particularly like the lazy way of counting change example (also works for 
picking items off a menu).


The code below show 3 approaches :
 a function for computing the coins used in each way as a verbose list
 a function for computing just the total number of ways
 a simply Monoid that does both at once, which a pretty summary display
And it has a short but user friendly main function that drives it.

The method used is simple.  It considers each value of coin in turn, this loop 
is done by the foldr.  The value being folded is a list where the index into the 
list is an amount for which change is being made; the value at that list index 
is the list or count of the ways to make that amount using the coins considered 
so far.


These exploit laziness since the returned lists are infinite and since 'result' 
is defined recursively for each different value of coin.


The example of defining a Monoid is a clear abstraction or generalization of the 
first two functions.



-- This demonstrates a way to find every eay to make change for a
-- given total using a set of coins.
--
-- By Chris Kuklewicz, Public Domain
import System.Environment(getArgs)
import Control.Exception as E(catch)
import Control.Monad(when)
import Data.List(group)
import Data.Monoid(Monoid(mempty,mappend))

computeListOfWays :: [Int] - [[[Int]]]
computeListOfWays coins = foldr includeValue noValues coins
  where noValues = [] : repeat []
includeValue value oldResult =
  let (unchangedResult,changedResult) = splitAt value oldResult
  result = unchangedResult ++
   zipWith (++) changedResult (map addCoin result)
  addCoin = map (value:)
  in result

computeCountOfWays :: [Int] - [Integer]
computeCountOfWays coins = foldr includeValue noValues coins
  where noValues = 1 : repeat 0
includeValue value oldResult =
  let (unchangedResult,changedResult) = splitAt value oldResult
  result = unchangedResult ++
   zipWith (+) changedResult result
  in result

computeWays :: [Int] - [Ways]
computeWays coins = foldr includeValue noValues coins
  where noValues = Ways [[]] 1 : repeat mempty
includeValue value oldResult =
  let (unchangedResult,changedResult) = splitAt value oldResult
  result = unchangedResult ++
   zipWith mappend changedResult (map addCoin result)
  addCoin (Ways list count) = Ways (map (value:) list) count
  in result

data Ways = Ways [[Int]] Integer

instance Monoid Ways where
  mempty = Ways [] 0
  mappend (Ways list1 count1) (Ways list2 count2) = Ways (list1++list2) 
(count1+count2)

instance Show Ways where
  show (Ways list count) = unlines (map summary list) ++ Count of Ways =  ++ show count 
++ \n
where summary = show . map (\sub - (length sub,head sub)) . group


coins_US :: [Int]
coins_US = [1,5,10,25,50]

coins_UK :: [Int]
coins_UK = [1,2,5,10,20,50]

main = do
  args - getArgs
  case args of
[] - error Pass a number of cents for which to count ways of making 
change
[x] - do n - E.catch (readIO x) (const (error The argument passed needs to be 
a number))
  when (n0) (error The argument passed needs to be a non-negative 
number)
  print (computeWays coins_US !! n)
_ - error Too many parameters, need just one number


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


[Haskell-cafe] Internships at GHC HQ

2008-01-25 Thread Simon Peyton-Jones
Would you be interested in working at Microsoft Research for three months?  If 
so, you might want to think about applying for an internship.

Simon and I are looking for interns, starting in summer 2008.  Lots of 
background info here:
http://hackage.haskell.org/trac/ghc/wiki/Internships
including a bunch of possible projects, although you may also have ideas of 
your own.

But the bottom line is
- apply by end Feb 2008 for this round
- tell one of us that you have done so

(None of this is restricted to Haskell stuff.  You can apply to work at any 
Microsoft Research lab, on any topic.  But there are a lot of applicants, so 
you are more likely to be successful if you are fairly specific about who at 
MSR you'd like to work with and why, and contact that person to say that you've 
applied.)

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


Re: [Haskell-cafe] hxt memory useage

2008-01-25 Thread Ketil Malde
Matthew Pocock [EMAIL PROTECTED] writes:

 I've been using hxt to process xml files. Now that my files are getting a bit 
 bigger (30m) I'm finding that hxt uses inordinate amounts of memory.
  :
 Is this a known issue?

Yes.  I parse what I suppose are rather large XML files (the largest
so far is 26GB), and ended up replacing HXT code with TagSoup.  I also
needed to use concurrency[1].  XML parsing is still slow, typically
consuming 90% of the CPU time, but at least it works without blowing
the heap. 

While I haven't tried HaXML, there is IMO a market opportunity for a
fast and small XML library, and I'd happily trade away features like
namespace support or arrows interfaces for that.

-k

[1] http://www.mail-archive.com/haskell-cafe@haskell.org/msg31862.html
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fwd: ByteString Parsec clone

2008-01-25 Thread Isaac Dupree

Johan Tibell wrote:

I tried to get Dan's thoughts on cloning parts of the Parsec interface
and some of the documentation but none of the emails addresses I've
tried seem to work. What's allowed when it comes to duplicating
something like an API? What about the documentation? I intend it to be
released under BSD3 which I believe is used for Parsec as well.


legally, since it's released under BSD, you're allowed to do all that 
(as long as you don't delete the bit of attribution that the BSD 
requires :-)


although a friendly attempt to contact him might be nice anyway, but 
don't worry too much if he's disappeared from the face of cyberspace, is 
the usual practice, I believe.




Anyone know how I can reach Dan?


not me

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


[Haskell-cafe] running into an unresolved linker error on RHEL 5

2008-01-25 Thread Galchin Vasili
Hello,

  I am building the unix-2.2.0.0. The linker is failing with -lgmp. I set
export LD_LIBRARY_ATH=/bin:/usr/lib. I did a ls -l /usr/lib/*gmp* and I
can see:

libgmp.so.3

libgmp.so.3.3.3

libgmpxx.so.3

libgmpxx.so.3.0.5, i.e. either gmp shared objects and whatever the gmp xx
shared objects are. So why is my link of unix-2.2.0.0 failing in
DynamicLinker?

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


[Haskell-cafe] HList error with hFoldr

2008-01-25 Thread Denis Bueno
Hello all,

I'm doing some machine learning in Haskell and have run into a
problem.  I have a generic distance function (declare in the
MetricSpace) typeclass that returns the distance between two things as
a number.  I frequently will be working with heterogeneous collections
of data, and if possible I'd like to write the distance function
(overloaded) once for all.  At the moment, I'm using HList to
represent the collections of data uniformly.

I wrote the following as a sanity check but I can't even get it to
compile.  The effect I'd like is that I can call `dist` on any two
HLists which have the correct, corresponding element types in the
correct positions, and `dist` will be recursively invoked to calculate
the typical euclidean distance (squared sum of individual element
distances, and at the and taking the square root).

My attempt at doing this follows.  For the moment my HLists only
contain Ints.  I'm using GHC 6.8.2 and HList 0.1.


import HList

class (Num i) = MetricSpace e i where
dist :: e - e - i

instance Num i = MetricSpace Int i where
x `dist` y = fromIntegral $ abs (y - x)

data ApplyDistSum = ApplyDistSum
instance (MetricSpace e r) = Apply ApplyDistSum ((e, e), r) r where
apply _ (p, v) = v + uncurry dist p

-- Why should the following generate an error?
testApplyDistSum = hFoldr ApplyDistSum 0 ((4,4) .*. hNil)
{- The error:

/Users/denbuen/edu/cornell/meng/classes/cs678/code/practice/Knn.hs:53:19:
No instance for (Apply ApplyDistSum ((t, t1), r1) r)
  arising from a use of `hFoldr'
   at
/Users/denbuen/edu/cornell/meng/classes/cs678/code/practice/Knn.hs:53:19-56
Possible fix:
  add an instance declaration for
  (Apply ApplyDistSum ((t, t1), r1) r)
In the expression: hFoldr ApplyDistSum 0 ((4, 4) .*. hNil)
In the definition of `testApplyDistSum':
testApplyDistSum = hFoldr ApplyDistSum 0 ((4, 4) .*. hNil)

-}

Thanks in advance.

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


[Haskell-cafe] NDP

2008-01-25 Thread Stephan Friedrichs

Hi all,

is someone familiar with compiling ndp (nested data parallel Haskell), 
Speed with less convenience-version?


I followed the guide at 
http://www.haskell.org/haskellwiki/Data_Parallel_Haskell/PackageNDP but 
executing make in the examples directory issues the following error:


(.text+0x8d5): undefined reference to 
`__stginit_parallelzm1zi0zi0zi0_ControlziParallelziStrategies_'


manually compiling the dotp example on the link mentioned above doesn't 
work either:


[...]

(.data+0x5c): undefined reference to 
`ndp_DataziArrayziParallelziUnliftedziFlatziUArr_zdf14_closure'

DotP.o: In function `sz3_srt':
(.data+0x88): undefined reference to 
`ndp_DataziArrayziParallelziUnliftedziFlatziBasics_toU_closure'

DotP.o: In function `sz3_srt':
(.data+0x8c): undefined reference to 
`ndp_DataziArrayziParallelziUnliftedziFlatziUArr_zdf14_closure'

/home/sfriedrichs/ghc/rts/libHSrts.a(Main.o): In function `real_main':
Main.c:(.text+0x12): undefined reference to `__stginit_ZCMain'
Main.c:(.text+0x2c): undefined reference to `ZCMain_main_closure'

Does someone know, what's wrong? I'm using ghc-6.9.20080124 as source 
base (which compiled and works just fine).


//Stephan

--

Früher hieß es ja: Ich denke, also bin ich.
Heute weiß man: Es geht auch so.

 - Dieter Nuhr



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


[Haskell-cafe] Re: [darcs-devel] announcing darcs 2.0.0pre3

2008-01-25 Thread David Roundy
On Wed, Jan 23, 2008 at 03:26:51PM +, Simon Marlow wrote:
 There are still times when I see nothing happening, for example in the 
 unpull test on the GHC repo (see previous messages), the last progress 
 message I get is
 
 Reading patches in /64playpen/simonmar/ghc-darcs2 17040
 
 and it sits there for 7-8 seconds before completing.  Does this maybe shed 
 any light on why this unpull is 2 times slower than darcs1?

I've finally got an idea what's causing this.  Actually, there are three
operations in which the hashed repositories don't scale quite as well as
the old format--all of which are pretty fast, so it's only visible on
huge repositories like yours.

The first two scale with the number of files and directories in the
repository, and both are essentially garbage collecting of the pristine
cache.

One goes through the _darcs/pristine.hashed/ directory and compares each
file there with a list of files that should be there, deleting those that
aren't present.  This is currently O(N^2) in the number of files and
directories in the repository, because we use a list to do this set
comparison.  Using Data.Set should make this O(NlogN) which probably is
more than enough to make this negligible.  It's already pretty fast, even
on the ghc repo, so this may not even be noticeable.

The second is similar to the first.  It's when we go through the global
cache to remove any unused files.  Here we use the link count, and remove
any that have a link count of 1.  This means running stat on each file to
get the link count, so this is only O(N) where N is the total number of
distinct files and directories (i.e. having different hashes) present in
*all* repositories that you use.  It scales better than the previous one,
but if stat is slow on the cache, or if you've got very many different
large repositories, it could be slow.

The third (and possibly largest) issue is the writing of the inventory
files.  This is (thankfully) independent of the number or size of files in
the repository, and only depends on the number of patches and tags.  It's
roughly O(N+M) where N is the number of patches and tags (with a different
prefactor on the two, but who cares?), and M is the number of new or
modified patches.  This isn't *bad* scaling, but when you've got 17k
patches, O(N) adds up.  This is most likely the primary culprit, but is
tricky to fix, since as far as I can imagine, we'd need to change the
PatchSet data type (currently just a nested RL list) to cache the hash
values, and change all functions manipulating them to invalidate the cache
when they make changes.  :(

I've added progress reporting to all three of these (and it seems like it's
working).  All three could be sped up in some way (the second, perhaps just
by avoiding writing pristine files to the global cache, or failing to
clean them up).  But I'd rather hear from you where the pain is before
going ahead, since I've got more work right now than I can handle.

Also, if you want (way!) more information when tracking down timings, the
progress reporting now interacts with the --debug flag to generate enough
data to kill a horse.  You could also add the --timings flag, which will
add some timestamps (alas, with only 1s resolution) that might be helpful.
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] realtime garbage collector for ghc (was: Why functional programming matters)

2008-01-25 Thread Stefan Kersten

On 25.01.2008, at 00:04, Evan Laforge wrote:

Well... ghc still has a single-threaded garbage collector, so all the
par threads must stop for garbage collection.  So scaling to the
level of a cluster would be significantly sub-linear.


A real time incremental gc would be really cool.  Some people claim
they exist, but which languages have one?


james mccartney's supercollider [1] has a non-copying incremental  
collector based on [2], though not a parallel one.


btw, is an implementation of the incremental collector described in  
[3] available somewhere? are there any plans to incorporate it into  
future ghc versions?


sk

[1] http://supercollider.sourceforge.net
[2] P. R. Wilson and M. S. Johnstone. Real-time non-copying garbage  
collection. In ACM OOPSLA Wsorkshop on Memory Management and Garbage  
Collection, 1993.
[3] A. M. Cheadle, A. J. Field, S. Marlow, S. L. P. Jones, and R. L.  
While. Exploring the barrier to entry: incremental generational  
garbage collection for haskell. In ISMM ’04: Proceedings of the 4th  
international symposium on Memory management, pages 163–174, New  
York, NY, USA, 2004. ACM.


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


Re: [Haskell-cafe] Fwd: ByteString Parsec clone

2008-01-25 Thread Johan Tibell
 legally, since it's released under BSD, you're allowed to do all that
 (as long as you don't delete the bit of attribution that the BSD
 requires :-)

As a practical matter. How do you manage attributions. Can you put a
other-project.LICENSE file which is a copy of the other projects
LICENSE file in the root of your project or do you have to keep track
of intra file copyright (i.e. this snippet was written by this person,
etc.)?

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


[Haskell-cafe] ANN: bytestringparser-0.2, a Parsec-like parser for lazy ByteStrings

2008-01-25 Thread Bryan O'Sullivan
Some time ago, Jeremy Shaw wrote a Parsec clone for lazy ByteStrings.
I've been using it for a while, and have made substantial changes to it
along the way.

It's very fast, using the same manual unpacking trick as the binary
package to keep performance nippy.  It also integrates with the latest
flava in parsing combinators, Control.Applicative, providing instances
of the Applicative and Alternative typeclasses.

The API is rather smaller than that of Parsec, but it's more than
adequate for parsing e.g. text-based network protocols.

Download:

http://hackage.haskell.org/packages/archive/bytestringparser/0.2/bytestringparser-0.2.tar.gz

Haddocks:

http://darcs.serpentine.com/bytestringparser/dist/doc/html/bytestringparser/Text-ParserCombinators-ByteStringParser.html

Darcs repository:

darcs get http://darcs.serpentine.com/bytestringparser

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


[Haskell-cafe] Re: hxt memory useage

2008-01-25 Thread Rene de Visser
Matthew Pocock [EMAIL PROTECTED] schrieb im Newsbeitrag 
news:[EMAIL PROTECTED]
 On Thursday 24 January 2008, Albert Y. C. Lai wrote:
 Matthew Pocock wrote:
  I've been using hxt to process xml files. Now that my files are getting 
  a
  bit bigger (30m) I'm finding that hxt uses inordinate amounts of 
  memory.
  I have 8g on my box, and it's running out. As far as I can tell, this
  memory is getting used up while parsing the text, rather than in any
  down-stream processing by xpickle.
 
  Is this a known issue?

 Yes, hxt calls parsec, which is not incremental.

 haxml offers the choice of non-incremental parsers and incremental
 parsers. The incremental parsers offer finer control (and therefore also
 require finer control).

 I've got a load of code using xpickle, which taken together are quite an
 investment in hxt. Moving to haxml may not be very practical, as I'll have 
 to
 find some eqivalent of xpickle for haxml and port thousands of lines of 
 code
 over. Is there likely to be a low-cost solution to convincing hxt to be
 incremental that would get me out of this mess?

 Matthew

I don't think so. Even if you replace parsec, HXT is itself not incremental. 
(It stores the whole XML document in memory as a tree, and the tree is not 
memory effecient.

Still I am a bit surprised that you can't parse 30m with 8 gig memory.

This was discussed here before, and I think someone benchmarked HXT as using 
roughly 50 bytes of memory per 1 byte of input.
i.e. HXT would then be using about 1.5 gig of memory for your 30m file.

Rene. 



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


Re: [Haskell-cafe] Why functional programming matters

2008-01-25 Thread Michael Reid

Yaakov Nemoy wrote:


I'm still very much a newbie, but the one thing that struck me as the
best feature coming from Python is the static typing.  Changing the
type of a function in Python will lead to strange runtime errors that
take some work to debug, whereas, when I tinker with a program in
Haskell, I already know it will work once it compiles.



I'm quite new to Haskell as well and I must echo this sentiment. The 
mainstream has somewhat realized that its a waste of time to tell the 
compiler the type of _everything_. Learning Haskell has completely 
reversed my feeling that static typing is an old outdated idea. The 
power of Haskell's type system makes it feel like you are programming in 
a dynamic language to some degree, yet all of it is type-checked, and 
that is just *really* cool.


Honestly, when I first started reading a Haskell tutorial I was 
convinced that it was an runtime-typed language like Python. When the 
tutorial moved on to explain that it is statically typed I could barely 
believe it.


The second thing I might want to highlight is the power of monads and 
other techniques like arrows and FRP.


Granted, these are not easy concepts to impart in a talk, but I think 
they were really an important discovery in FP as they deal with the 
problem of IO in such a beautifully orthogonal way. Following on that, 
more advanced structures like arrows and how all of this can contribute 
to really powerful DSLs I think is a pretty big selling point.


Actually, come to think of it, one great way to show off the language is 
to show off the power of some of the libraries that have been written. 
For example, show how easily a parser can  be created w/ Parsec; or show 
 an example of FRP w/ Yampa. These examples will likely tantalize the 
programmers in the audience to want to learn more.


Good luck!

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


Re: [Haskell-cafe] hxt memory useage

2008-01-25 Thread Neil Mitchell
Hi

One of the problems with XML parsing is nesting. Consider this fragment:

foolots of text/foo

The parser will naturally want to track all the way down to the
closing /foo in order to check the document is well formed, so it
can put it in a tree. The problem is that means keeping lots of text
in memory - often the entire document. TagSoup works in a lazy
streaming manner, so would parse the above as:

[TagOpen foo [], TagText lots of text, TagClose foo]

i.e. it hasn't matched the foo's, and can return the TagOpen before
even looking at the text.

 XML parsing is still slow, typically
 consuming 90% of the CPU time, but at least it works without blowing
 the heap.

I'd love TagSoup to go faster, while retaining its laziness. A basic
profiling doesn't suggest anything obvious, but I may have missed
something. It's more likely that it would be necessary to prod at the
Core level, or move to supporting both (Lazy)ByteString and [Char].

Thanks

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


Re: [Haskell-cafe] Evolutionary Computing

2008-01-25 Thread Dusan Kolar

Hello,

I don't know about math, but a practical usage seems to be in the 
reconfigurable hardware (FPGA). See web-page of my colleague, where is 
list of his papers on the topic.


http://www.fit.vutbr.cz/~sekanina/pubs.php

Dusan

PR Stanley wrote:

Hi
What does the list think of EC? Genetic algorithm is apparently the 
latest thing.

Is EC mathematically reasonable?
Paul


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


Re: [Haskell-cafe] Evolutionary Computing

2008-01-25 Thread Alex Young

Dusan Kolar wrote:

Hello,

I don't know about math, but a practical usage seems to be in the 
reconfigurable hardware (FPGA). See web-page of my colleague, where is 
list of his papers on the topic.


http://www.fit.vutbr.cz/~sekanina/pubs.php
These people use GAs for optimising water networks (and, more 
importantly, maintenance of water networks):


http://optimatics.com/go/case-studies-andamp-testimonials

Their tools are all C++, though.

--
Alex



Dusan

PR Stanley wrote:

Hi
What does the list think of EC? Genetic algorithm is apparently the 
latest thing.

Is EC mathematically reasonable?
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] hxt memory useage

2008-01-25 Thread Don Stewart
ketil+haskell:
 Matthew Pocock [EMAIL PROTECTED] writes:
 
  I've been using hxt to process xml files. Now that my files are getting a 
  bit 
  bigger (30m) I'm finding that hxt uses inordinate amounts of memory.
   :
  Is this a known issue?
 
 Yes.  I parse what I suppose are rather large XML files (the largest
 so far is 26GB), and ended up replacing HXT code with TagSoup.  I also
 needed to use concurrency[1].  XML parsing is still slow, typically
 consuming 90% of the CPU time, but at least it works without blowing
 the heap. 
 
 While I haven't tried HaXML, there is IMO a market opportunity for a
 fast and small XML library, and I'd happily trade away features like
 namespace support or arrows interfaces for that.

So this is a request for an xml-light based on lazy bytestrings, designed
for speed at all costs?

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


Re: [Haskell-cafe] realtime garbage collector for ghc

2008-01-25 Thread Andrew Cheadle

Hi Stefan,


A real time incremental gc would be really cool.  Some people claim
they exist, but which languages have one?


james mccartney's supercollider [1] has a non-copying incremental 
collector based on [2], though not a parallel one.


btw, is an implementation of the incremental collector described in 
[3] available somewhere? are there any plans to incorporate it into 
future ghc versions?


sk

[1] http://supercollider.sourceforge.net
[2] P. R. Wilson and M. S. Johnstone. Real-time non-copying garbage 
collection. In ACM OOPSLA Wsorkshop on Memory Management and Garbage 
Collection, 1993.
[3] A. M. Cheadle, A. J. Field, S. Marlow, S. L. P. Jones, and R. L. 
While. Exploring the barrier to entry: incremental generational 
garbage collection for haskell. In ISMM ’04: Proceedings of the 4th 
international symposium on Memory management, pages 163–174, New York, 
NY, USA, 2004. ACM.


The collector in [3] isn't in a production version of GHC for several 
reasons, mainly because I finished it prior to significant reworking of 
GHC's backend (C-- target etc), and while finishing my PhD I couldn't 
devote the time to keeping it current - it is a massive engineering 
task! Furthermore, the scheduling of work-based increments are 
problematic and I only made a preliminary start with time-based 
collection. That said:


Our current work here at Imperial has focussed on implementing exactly 
what we did for GHC in Java, targetting the Jikes RVM, and we've made 
alot of progress (*shameless plug*, check out our paper at VEE 2008: /A 
Method Specialisation and Virtualised Execution Environment for Java).


/With this work nearing completion my attention is turning back to GHC 
but with particular focus on concurrency, and multi-core / parallel 
collection and the STM world... I haven't ruled out the collector being 
incremental too, so I wouldn't be surprised if I resurrect this code 
base... Of course, these things take time and I have other commitments...


I know Simon has been working on parallel collection and I would expect 
this to be more generally useful than a single-threaded incremental 
collector, so I'll leave it to him to say how that's coming on...


Cheers

Andy
//

--
*
*  Andrew Cheadleemail:  [EMAIL PROTECTED] *
*  Department of Computing   http://www.doc.ic.ac.uk/~amc4/ *
*  Imperial College London  *
*

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


Re: [Haskell-cafe] Internships at GHC HQ

2008-01-25 Thread Vimal
On 25/01/2008, Simon Peyton-Jones [EMAIL PROTECTED] wrote:
 Would you be interested in working at Microsoft Research for three months?  
 If so, you might want to think about applying for an internship.


I would love to!
But here are some questions:

1. Do I _necessarily_ have to come to MSR Cambridge to do my research?
Is it possible that I stay in India and do the work?
Our institute wants interns (that counts as a course) to be done ONLY in India.

2. What background experience do you expect your intern to have? Does
an undergraduate have enough experience? (undergrad who has done a
course on Language Translators, say).


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


Re: [Haskell-cafe] realtime garbage collector for ghc (was: Why functional programming matters)

2008-01-25 Thread Dan Licata

See also

  A parallel, real-time garbage collector
  Perry Cheng and Guy Blelloch
  PLDI 2001

This was implemented in the TILT compiler for SML (which, to be fair, is
more of a research vehicle than a programmer-friendly implementation).

-Dan

On Jan25, Stefan Kersten wrote:
 On 25.01.2008, at 00:04, Evan Laforge wrote:
 Well... ghc still has a single-threaded garbage collector, so all the
 par threads must stop for garbage collection.  So scaling to the
 level of a cluster would be significantly sub-linear.
 
 A real time incremental gc would be really cool.  Some people claim
 they exist, but which languages have one?
 
 james mccartney's supercollider [1] has a non-copying incremental  
 collector based on [2], though not a parallel one.
 
 btw, is an implementation of the incremental collector described in  
 [3] available somewhere? are there any plans to incorporate it into  
 future ghc versions?
 
 sk
 
 [1] http://supercollider.sourceforge.net
 [2] P. R. Wilson and M. S. Johnstone. Real-time non-copying garbage  
 collection. In ACM OOPSLA Wsorkshop on Memory Management and Garbage  
 Collection, 1993.
 [3] A. M. Cheadle, A. J. Field, S. Marlow, S. L. P. Jones, and R. L.  
 While. Exploring the barrier to entry: incremental generational  
 garbage collection for haskell. In ISMM ’04: Proceedings of the 4th  
 international symposium on Memory management, pages 163–174, New  
 York, NY, USA, 2004. ACM.
 
 ___
 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] Internships at GHC HQ

2008-01-25 Thread Dan Licata
A further plug:

I did an internship with Simon PJ last summer (implementing view
patterns in GHC, among other things), and this is a great opportunity if
you're interested in PL research.  There is a lot of interesting work
going on at MSR Cambridge, the atmosphere is very friendly, and
Cambridge is a lovely place to spend a summer.

If anyone wants an intern's-eye view of the experience, feel free to
e-mail me!

-Dan

On Jan25, Simon Peyton-Jones wrote:
 Would you be interested in working at Microsoft Research for three months?  
 If so, you might want to think about applying for an internship.
 
 Simon and I are looking for interns, starting in summer 2008.  Lots of 
 background info here:
 http://hackage.haskell.org/trac/ghc/wiki/Internships
 including a bunch of possible projects, although you may also have ideas of 
 your own.
 
 But the bottom line is
 - apply by end Feb 2008 for this round
 - tell one of us that you have done so
 
 (None of this is restricted to Haskell stuff.  You can apply to work at any 
 Microsoft Research lab, on any topic.  But there are a lot of applicants, so 
 you are more likely to be successful if you are fairly specific about who at 
 MSR you'd like to work with and why, and contact that person to say that 
 you've applied.)
 
 Simon
 ___
 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] Internships at GHC HQ

2008-01-25 Thread Tim Chevalier
On 1/25/08, Dan Licata [EMAIL PROTECTED] wrote:
 A further plug:

 I did an internship with Simon PJ last summer (implementing view
 patterns in GHC, among other things), and this is a great opportunity if
 you're interested in PL research.  There is a lot of interesting work
 going on at MSR Cambridge, the atmosphere is very friendly, and
 Cambridge is a lovely place to spend a summer.

 If anyone wants an intern's-eye view of the experience, feel free to
 e-mail me!


I second most parts of this (including the feel free to email me
part).  I hear that the summer is busiest with respect to interns,
but those who can arrange it with their graduate programs ought to
consider applying for an internship during the school year. I don't
know what things are like now, but I found that there were plenty of
other interns around to keep me company even during the fall, and
Cambridge is a lovely place to spend an autumn as well.

Cheers,
Tim

-- 
Tim Chevalier * http://cs.pdx.edu/~tjc * Often in error, never in doubt
The more you talk, the more I get / a sense of something that hasn't
happened yet / The more you talk, the more I want to know / the way
I'll remember you when I go. -- Ani DiFranco
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Why functional programming matters

2008-01-25 Thread Wolfgang Jeltsch
Am Freitag, 25. Januar 2008 03:35 schrieb Conal Elliott:
 […]

 See http://haskell.org/haskellwiki/Reactive and http://haskell.org/yampa/ .

Or better http://haskell.org/haskellwiki/Functional_Reactive_Programming 
which has come into existence recently.

 […]

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