[Haskell-cafe] Simple implementations of the lambda calculus

2006-11-12 Thread Lennart Augustsson
Some time ago I made a little experiment and implemented an  
interpreter for the lambda-calculus in Haskell.  The only reason was  
that I wanted to try different ways of doing it.  So I did it using  
simple substitution (i.e., as the textbooks describe it), unique  
identifiers, deBruijn indicies, and higher order abstract syntax.


You can get the code from http://darcs.augustsson.net/Darcs/Lambda/  
or just check out small paper at http://darcs.augustsson.net/Darcs/ 
Lambda/top.pdf


-- Lennart

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


Re: [Haskell-cafe] Translating Haskell to VHDL. What approach to follow?

2006-11-12 Thread Alfonso Acosta

For .hi files just compile it with Yhc and take a look at the .hi file
it creates, they are plain text. If they are top level functions
(which they certainly are, I guess) this should be all you need.
Another approach is to get the type information out of Hugs with the
:t command line prod. I've done this before in another project.


Sorry for the delay answering. I didn't (and still won't) have access
to the Internet for a few days but Ill try it and tell you if it
worked once I'm back to normality.

Thanks,

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


[Haskell-cafe] ByteString FFI

2006-11-12 Thread Donn Cave
How do people like to set up their foreign I/O functions to return
ByteStrings?  I was a little stumped over this yesterday evening,
while trying to write ` recv :: Socket - Int - Int - ByteString '

Doc says `Byte vectors are encoded as strict Word8 arrays of bytes,
held in a ForeignPtr, and can be passed between C and Haskell with
little effort.'  Which sounds perfect - I'm always up for `little effort'!

CString doesn't seem like the right thing for socket results, because
the data shouldn't be NUL-terminated, and I might want to realloc when
the returned data doesn't fill the buffer.  I don't see any other
Ptr-related function or constructor in the documentation - am I missing
something there?

Thanks,

Donn Cave, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ByteString FFI

2006-11-12 Thread Duncan Coutts
On Sun, 2006-11-12 at 10:49 -0800, Donn Cave wrote:
 How do people like to set up their foreign I/O functions to return
 ByteStrings?  I was a little stumped over this yesterday evening,
 while trying to write ` recv :: Socket - Int - Int - ByteString '
 
 Doc says `Byte vectors are encoded as strict Word8 arrays of bytes,
 held in a ForeignPtr, and can be passed between C and Haskell with
 little effort.'  Which sounds perfect - I'm always up for `little effort'!
 
 CString doesn't seem like the right thing for socket results, because
 the data shouldn't be NUL-terminated, and I might want to realloc when
 the returned data doesn't fill the buffer.  I don't see any other
 Ptr-related function or constructor in the documentation - am I missing
 something there?

packCStringLen :: CStringLen - ByteString

(type CStringLen = (Ptr CChar, Int))

http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-ByteString.html#v%3ApackCStringLen

So if you know the length and the pointer to the beginning of the buffer
then it's just packCStringLen (ptr, len)

Of course you're not allowed to change the buffer after this, if you are
using a mutable buffer then you'll have to make a copy:

copyCStringLen :: CStringLen - IO ByteString

Duncan

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


[Haskell-cafe] GHCi 6.6 tab-completion of source file paths not working.

2006-11-12 Thread Daniel McAllansmith
Hi.

I've just installed GHC 6.6 on an amd64 running a gentoo linux distribution.

With GHCi from 6.4.2 I could run ghci then do

Prelude :l Foo/Bar.hs

by hitting tab after Foo to complete the path to Bar.hs

This no longer works, hitting tab only shows what's in the pwd.


If I run ghci Foo/Bar.hs then I can :r fine and I can do a :l Foo.Bar using 
tab-completion to complete the module name.
Tab completion of in-scope functions looks to be working fine.

Has anybody else experienced this problem?

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


Re: [Haskell-cafe] (twice head) (twice tail)

2006-11-12 Thread Claus Reinke

not a solution to your problem, but covers all your tests,
as well as one more that would inevitably have followed:-)

cheers,
claus



Twice.hs
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] best Linux for GHC?

2006-11-12 Thread Bulat Ziganshin
Hello haskell-cafe,

Now i'm consider installation of some Linux version at my box. My
friend offered me 3 variants: SuSe, Fedora Core 5, free variant of
RedHat (i can't remember its name, may be Ubuntu?)

what may be best for GHC-based development? in particular, i want to
compile Haskell itself

i suspect that it is a really dumb question, and GHC will work great
just with any linux i can find :)

-- 
Best regards,
 Bulat  mailto:[EMAIL PROTECTED]

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


[Haskell-cafe] what GUI library should i select?

2006-11-12 Thread Bulat Ziganshin
Hello haskell-cafe,

afaik, there are just two good enough libs - wxHaskell and GtkHs. can
anyone point (or write) detailed comparison of their features? i plan
to write large GUI program in Haskell and want to select best one.
the requirements that i can imagine at this moment is the following:

* my main target is Windows but ability to compile the same code both
for Windows and Linux would be a plus
* the program developed is a sort of advanced file manager, so i need
treeview, table view and tabbed view controls
* user likes beauty, so various bells-and-whistles are welcomed. in
particular, it would be great to have skinnable interface
* use of resource file for all texts to make internalization easier

-- 
Best regards,
 Bulat  mailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] best Linux for GHC?

2006-11-12 Thread Donald Bruce Stewart
bulat.ziganshin:
 Hello haskell-cafe,
 
 Now i'm consider installation of some Linux version at my box. My
 friend offered me 3 variants: SuSe, Fedora Core 5, free variant of
 RedHat (i can't remember its name, may be Ubuntu?)
 
 what may be best for GHC-based development? in particular, i want to
 compile Haskell itself
 
 i suspect that it is a really dumb question, and GHC will work great
 just with any linux i can find :)
 
 -- 

Gentoo or Debian, I suspect, since then you get the #haskell-gentoo
team, and Igloo, keeping things up to date :)

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


Re: [Haskell-cafe] what GUI library should i select?

2006-11-12 Thread Duncan Coutts
On Mon, 2006-11-13 at 02:50 +0300, Bulat Ziganshin wrote:
 Hello haskell-cafe,
 
 afaik, there are just two good enough libs - wxHaskell and GtkHs. can
 anyone point (or write) detailed comparison of their features? i plan
 to write large GUI program in Haskell and want to select best one.
 the requirements that i can imagine at this moment is the following:

I maintain Gtk2Hs, so I can tell you about that.

Much of the difference comes down to the difference between Gtk+ and
wxWidgets. You can read detailed comparisons between them elsewhere. The
main touted advantage of wxWidgets is that it is a wrapper over
different 'native' widget sets on each platform. This is also it's main
disadvantage as it means the semantics of the API are not always 100%
portable, it adds an extra indirection layer and it can't provide all
the features of the native widget set as it has to provide a lowest
common denominator API.

On the other hand Gtk+ is a portable implementation that uses themes to
provide a 'native' look (on windows it uses the native WinXP themeing
dll). This means the look is not always perfect (though it has improved
dramatically recently) but the semantics are much better preserved
between platforms.

As for the bindings, there's a great deal of similarity. One difference
is in memory management. Gtk+ was designed while keeping in mind the
goal of having bindings in garbage-collected languages where as
wxWidgets uses ordinary C++ object lifetime management. Basically this
means that with Gtk2Hs, if you get a segfault then it was my fault and a
bug in Gtk2Hs. With wxHaskell you can get into situations where you can
get a segfault and there's nothing wxHaskell can do about it.

Axel wrote more about that here:

http://haskell.org/gtk2hs/archives/2005/07/15/automatic-memory-management/

 * my main target is Windows but ability to compile the same code both
 for Windows and Linux would be a plus

Gtk2Hs works on both.

 * the program developed is a sort of advanced file manager, so i need
 treeview, table view and tabbed view controls

Gtk+ has quite a flexible tree/list widget. With the upcoming release
there is a new Haskell api to this to make it much easier to use and
more Haskell-like. The tree/list widget follows the model/view and the
view is very flexible in how it displays data from the model. You can
set arbitrary Haskell functions to map data from the model to attributes
of the cell renderers in the columns. There are also several different
cell renderers, eg simple text, check buttons, icons, combo boxes etc.

 * user likes beauty, so various bells-and-whistles are welcomed. in
 particular, it would be great to have skinnable interface

Gtk+ uses themes. Of course on windows the default theme is the same as
the native global theme. Similarly, on Linux it follows the global
Gtk/GNOME theme.

 * use of resource file for all texts to make internalization easier

If you use glade for the UI (which the recommended style) then it's
possible to internationalise it. This is how most of the Gtk/GNOME
programs do internationalisation of their UIs.

Duncan

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


Re: [Haskell-cafe] GHCi 6.6 tab-completion of source file paths not working.

2006-11-12 Thread Duncan Coutts
On Mon, 2006-11-13 at 12:02 +1300, Daniel McAllansmith wrote:
 Hi.
 
 I've just installed GHC 6.6 on an amd64 running a gentoo linux distribution.
 
 With GHCi from 6.4.2 I could run ghci then do
 
 Prelude :l Foo/Bar.hs
 
 by hitting tab after Foo to complete the path to Bar.hs
 
 This no longer works, hitting tab only shows what's in the pwd.
 
 
 If I run ghci Foo/Bar.hs then I can :r fine and I can do a :l Foo.Bar using 
 tab-completion to complete the module name.
 Tab completion of in-scope functions looks to be working fine.
 
 Has anybody else experienced this problem?

The tab completion was changed in GHC 6.6 so that it can tab-complete
Haskell identifiers. It's quite possible that in the change-over that
tab completion for files got broken. I suggest you file a bug report and
describe exactly the behaviour that you would expect.

Duncan

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


Re: [Haskell-cafe] best Linux for GHC?

2006-11-12 Thread Grady Lemoine

I use Ubuntu, which is a flavor of Debian.  It was pretty easy to
install, and it's intended to be friendly to new Linux users, while
not getting in the way of people who want to do more advanced things.
My only complaint Haskell-wise is that GHC 6.6 hasn't made it into the
package system yet; the latest available from the package system is
6.4.1, but you could always download 6.6 and compile it yourself if
necessary.

--Grady Lemoine

On 11/12/06, Bulat Ziganshin [EMAIL PROTECTED] wrote:

Hello haskell-cafe,

Now i'm consider installation of some Linux version at my box. My
friend offered me 3 variants: SuSe, Fedora Core 5, free variant of
RedHat (i can't remember its name, may be Ubuntu?)

what may be best for GHC-based development? in particular, i want to
compile Haskell itself

i suspect that it is a really dumb question, and GHC will work great
just with any linux i can find :)

--
Best regards,
 Bulat  mailto:[EMAIL PROTECTED]

___
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] what GUI library should i select?

2006-11-12 Thread Neil Mitchell

Hi Bulat,


afaik, there are just two good enough libs - wxHaskell and GtkHs. can
anyone point (or write) detailed comparison of their features? i plan
to write large GUI program in Haskell and want to select best one.
the requirements that i can imagine at this moment is the following:


I used to use wxHaskell. I wanted to write a GUI program using GHC
6.4.2 and was (disturbingly) shocked to find out that _neither_ of the
GUI toolkits had prebuilt packages that worked on Windows with GHC
6.4.2. I complained and within a day Duncan had done one for Gtk2Hs,
and to my knowledge wxHaskell still doesn't have such a packaged
version.

For this reason, I would recommend Gtk2Hs - the level of support and
maintainership is far better than wxHaskell at the moment. I
appreciate wxHaskell has new maintainers, but when picking a GUI
toolkit where you can't easily switch later, currently maintained is a
big bullet point for me!

Thanks

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


[Haskell-cafe] Re: A type class puzzle

2006-11-12 Thread Chung-chieh Shan
Yitzchak Gale [EMAIL PROTECTED] wrote in article [EMAIL PROTECTED] in 
gmane.comp.lang.haskell.cafe:
 replace0 :: a - a - a
 replace1 :: Int - a - [a] - [a]
 replace2 :: Int - Int - a - [[a]] - [[a]]

This message is joint work with Oleg Kiselyov.  All errors are mine.

Part of what makes this type-class puzzle difficult can be explained
by trying to write Prolog code to identify those types that the
general replace function can take.  We use an auxiliary predicate
repl(X0,X,Y0,Y), which means that X0 is int - applied the same number
of times to X as Y0 is [] applied to Y.

repl(X, X, Y, Y).
repl((int - X0), X, [Y0], Y) :- repl(X0, X, Y0, Y).

We can now write a unary predicate replace1(X0) to test if any given
type X0 is a valid type for the replace function.

replace1(X0) :- repl(X0, (Y - Y0 - Y0), Y0, Y).

Positive and negative tests:

?- replace1(bool - bool - bool).
?- replace1(int - bool - [bool] - [bool]).
?- replace1(int - int - bool - [[bool]] - [[bool]]).
?- replace1(int - int - int - [[int]] - [[int]]).
?- \+ replace1(bool - [bool] - [bool]).

The optimist would expect to be able to turn these Prolog clauses
into Haskell type-class instances directly.  Unfortunately, at least
one difference between Prolog and Haskell stands in the way: Haskell
overloading resolution does not backtrack, and the order of type-class
instances should not matter.  Suppose that we switch the two repl
clauses and add a cut, as follows:

repl((int - X0), X, [Y0], Y) :- !, repl(X0, X, Y0, Y).
repl(X, X, Y, Y).

Now the second-to-last test above

?- replace1(int - int - int - [[int]] - [[int]]).

fails, because repl needs to look ahead beyond the current argument
type to know that the third int in the type is not an index but a list
element.  This kind of ambiguity is analogous to a shift-reduce conflict
in parsing.

We could roll our own backtracking if we really wanted to, but let's
switch to the saner type family

   replace0 :: a - a - a
   replace1 :: Int - [a] - a - [a]
   replace2 :: Int - Int - [[a]] - a - [[a]]

where the old list comes before the new element.  The corresponding
Prolog predicate and tests now succeed, even with the switched and cut
repl clauses above.

replace2(X0) :- repl(X0, (Y0 - Y - Y0), Y0, Y).

?- replace2(bool - bool - bool).
?- replace2(int - [bool] - bool - [bool]).
?- replace2(int - int - [[bool]] - bool - [[bool]]).
?- replace2(int - int - [[int]] - int - [[int]]).
?- \+ replace2([bool] - bool - [bool]).

Regardless of this change, note that a numeric literal such as 2 in
Haskell can denote not just an Int but also a list, given a suitable Num
instance.  Therefore, the open-world assumption of Haskell type classes
forces us to annotate our indices with ::Int in Haskell.

Below, then, are the tests that we strive to satisfy.

   x1 = abc
   x2 = [ab, cde, fghi, uvwxyz]
   x3 = [[[i1 + i2 + i3 | i3 - [10..13]] | i2- [4..5]] | i1 - [(1::Int)..3]]

   test1:: String
   test1 = replace (1::Int) x1 'X'

   {- expected error reported
   test2:: [String]
   test2 = replace (1::Int) x2 'X'
   -}

   test3:: [String]
   test3 = replace (1::Int) x2 X

   test4:: [String]
   test4 = replace (2::Int) (1::Int) x2 'X'

   test5:: [[[Int]]]
   test5 = replace (2::Int) (0::Int) (1::Int) x3 (100::Int)

The remainder of this message shows two ways to pass these tests.  Both
ways require allowing undecidable instances in GHC 6.6.

   {-# OPTIONS -fglasgow-exts #-}
   {-# OPTIONS -fallow-undecidable-instances #-}

In the first way, the Replace type-class parses the desired type for
replace into a tuple of indices, in other words, a type-level list
of indices.  An auxiliary type-class Replace' then reverses this list.
Finally, another auxiliary type-class Replace'' performs the actual
replacement.

   class Replace'' n old new where
 repl'' :: n - old - new - old
   instance Replace'' () a a where
 repl'' () old new = new
   instance Replace'' n old new = Replace'' (n,Int) [old] new where
 repl'' (i,i0) old new =
   case splitAt i0 old of (h,[]   ) - h
  (h,th:tt) - h ++ repl'' i th new : tt

   class Replace' n n' old new where
 repl' :: n - n' - old - new - old
   instance Replace'' n old new = Replace' n () old new where
 repl' n () = repl'' n
   instance Replace' (n1,n2) n3 old new = Replace' n1 (n2,n3) old new where
 repl' n1 (n2,n3) = repl' (n1,n2) n3

   class Replace n a b c where
 repl :: n - a - b - c
   instance Replace' () n [old] new = Replace n [old] new [old] where
 repl = repl' ()
   instance Replace (i,n) a b c = Replace n i a (b-c) where
 repl i0 i = repl (i,i0)

   replace n = repl () n

The second way, shown below, eliminates the intermediate tuple of
indices used above.  This code doesn't require allowing undecidable
instances in Hugs, but it does use functional dependencies to coax
Haskell into applying the last Replace instance.

   class Replace old 

Re: [Haskell-cafe] ByteString FFI

2006-11-12 Thread Donald Bruce Stewart
donn:
 How do people like to set up their foreign I/O functions to return
 ByteStrings?  I was a little stumped over this yesterday evening,
 while trying to write ` recv :: Socket - Int - Int - ByteString '
 
 Doc says `Byte vectors are encoded as strict Word8 arrays of bytes,
 held in a ForeignPtr, and can be passed between C and Haskell with
 little effort.'  Which sounds perfect - I'm always up for `little effort'!
 
 CString doesn't seem like the right thing for socket results, because
 the data shouldn't be NUL-terminated, and I might want to realloc when
 the returned data doesn't fill the buffer.  I don't see any other
 Ptr-related function or constructor in the documentation - am I missing
 something there?

And for custom data (not just C strings), if the withCString* functions
don't quite fit, you can always pack the foreign Ptr into a ByteString
by stepping inside the ByteString constructor:

http://www.haskell.org/haskellwiki/Wc#Going_via_C

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


Re: [Haskell-cafe] what GUI library should i select?

2006-11-12 Thread Iván Pérez Domínguez
Neil Mitchell wrote:
 Hi Bulat,
 
 afaik, there are just two good enough libs - wxHaskell and GtkHs. can
 anyone point (or write) detailed comparison of their features? i plan
 to write large GUI program in Haskell and want to select best one.
 the requirements that i can imagine at this moment is the following:
 
 I used to use wxHaskell.

So did I. I tried gtk2hs as well. In my experience, gtk2hs is more
complicated. On the other hand, gtk2hs supports glade, I think.

wxHaskell seems to be easier to understand and to use. In my case, I
took a reversi game from haskell.org and did a sudoku game in a few
weeks (with no prior knowledge on wxHaskell).

 I wanted to write a GUI program using GHC
 6.4.2 and was (disturbingly) shocked to find out that _neither_ of the
 GUI toolkits had prebuilt packages that worked on Windows with GHC
 6.4.2. I complained and within a day Duncan had done one for Gtk2Hs,
 and to my knowledge wxHaskell still doesn't have such a packaged
 version.
 

I'm using Gentoo Linux. We obviously don't use prebuilt packaged
versions, but installing it is just doing emerge wxhaskell and
'playing the... waiting game'. Gtk2hs support under Gentoo is mostly
missing (the package is included, but doesn't work at all).

 For this reason, I would recommend Gtk2Hs - the level of support and
 maintainership is far better than wxHaskell at the moment. I
 appreciate wxHaskell has new maintainers, but when picking a GUI
 toolkit where you can't easily switch later, currently maintained is a
 big bullet point for me!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] what GUI library should i select?

2006-11-12 Thread Iván Pérez Domínguez
Bulat Ziganshin wrote:
 Hello haskell-cafe,
 
 afaik, there are just two good enough libs - wxHaskell and GtkHs. can
 anyone point (or write) detailed comparison of their features? i plan
 to write large GUI program in Haskell and want to select best one.
 the requirements that i can imagine at this moment is the following:
 
 * my main target is Windows but ability to compile the same code both
 for Windows and Linux would be a plus

with wxhaskell, you've got this one for sure.

 * the program developed is a sort of advanced file manager, so i need
 treeview, table view and tabbed view controls

this one too, I guess.

 * user likes beauty, so various bells-and-whistles are welcomed. in
 particular, it would be great to have skinnable interface

I did this in a sudoku game. I used the same schema as in the reversi
game (available at haskell.org).

 * use of resource file for all texts to make internalization easier

Last one I don't know.

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


Re: [Haskell-cafe] ByteString FFI

2006-11-12 Thread Donn Cave
On Mon, 13 Nov 2006, Donald Bruce Stewart wrote:

 And for custom data (not just C strings), if the withCString* functions
 don't quite fit, you can always pack the foreign Ptr into a ByteString
 by stepping inside the ByteString constructor:
 
 http://www.haskell.org/haskellwiki/Wc#Going_via_C

That's actually what I tried first, but in this particular situation
(ghc-6.4.1 / fps-0.7), PS apparently isn't exported?

The CStringLen approach works, except that the allocated data doesn't
get garbage-collected.  Just for the sake of experiment I tried a regular
CString with packMallocCString, and that didn't leak nearly as much memory -
but still some, in a simple loop where pack doesn't leak anything.

Thanks,
Donn Cave, [EMAIL PROTECTED]

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


Re: [Haskell-cafe] ByteString FFI

2006-11-12 Thread Donald Bruce Stewart
donn:
 On Mon, 13 Nov 2006, Donald Bruce Stewart wrote:
 
  And for custom data (not just C strings), if the withCString* functions
  don't quite fit, you can always pack the foreign Ptr into a ByteString
  by stepping inside the ByteString constructor:
  
  http://www.haskell.org/haskellwiki/Wc#Going_via_C
 
 That's actually what I tried first, but in this particular situation
 (ghc-6.4.1 / fps-0.7), PS apparently isn't exported?

Right, you'll want to grab the soon-to-be-tagged fps 0.8, which matches
that provided with ghc 6.6. It's in the darcs repo.

 The CStringLen approach works, except that the allocated data doesn't
 get garbage-collected.  Just for the sake of experiment I tried a regular
 CString with packMallocCString, and that didn't leak nearly as much memory -
 but still some, in a simple loop where pack doesn't leak anything.

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