Re: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-20 Thread Michael T. Richter
On Wed, 2007-20-06 at 15:21 +1000, Donald Bruce Stewart wrote:

 -- unsigned char *MD5(const unsigned char *d, unsigned long n, unsigned 
 char *md);
 foreign import ccall openssl/md5.h MD5 c_md5
 :: Ptr CChar - CULong - Ptr CChar - IO (Ptr Word8)



 ByteStrings were designed for this zero-copy passing of big data to C,
 by the way, so its a perfect fit.


I'm not so sure I like the idea of having to do this by passing it over
to C.  Crypto sounds like exactly the kind of application that would
require the certainty of FP reasoning.  Is there no way to make it work
reasonably efficiently in Haskell proper?

-- 
Michael T. Richter [EMAIL PROTECTED] (GoogleTalk:
[EMAIL PROTECTED])
I can see computers everywhere - except in the productivity statistics!
(Robert Solow)


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-20 Thread Donald Bruce Stewart
ttmrichter:
 
On Wed, 2007-20-06 at 15:21 +1000, Donald Bruce Stewart
wrote:
 
 -- unsigned char *MD5(const unsigned char *d, unsigned long n, un
 signed char *md);
 foreign import ccall openssl/md5.h MD5 c_md5
 :: Ptr CChar - CULong - Ptr CChar - IO (Ptr Word8)
 
 ByteStrings were designed for this zero-copy passing of big data to C
 ,
 by the way, so its a perfect fit.
 
I'm not so sure I like the idea of having to do this by

You don't *have* to do it via C, but you *can* do it, if you want.

passing it over to C.  Crypto sounds like exactly the kind
of application that would require the certainty of FP
reasoning.  Is there no way to make it work reasonably
efficiently in Haskell proper?

Sure, why not? We've a good native code compiler, after all. Write an
md5 over ByteString -- it should be pretty competitive. Here's a
reference C implementation to start from:

http://www.cse.unsw.edu.au/~dons/tmp/md5.c

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


Orthogonal Persistence in Haskell, was: Re: [Haskell-cafe] To yi or not to yi, is this really the question? A plea for a cooperative, ubiquitous, distributed integrated development system.

2007-06-20 Thread Pasqualino 'Titto' Assini
On Monday 18 June 2007 23:45:23 Claus Reinke wrote:

  Have you checked the prevayler-inspired approach implemented in HAppS ?

 no, do you have a reference? but i meant orthogonal persistence, as in
 all program parts can persist, including functions, thunks, types,.. once
 you start going down that route, the rigid globally static/dynamic
 distinction quickly becomes meaningless (instead one has locally
 static/dynamic phases of evaluating program parts, ie, one does a dynamic
 type check in each static phase, and if that succeeds, the immediately
 following dynamic phase will be type correct without further runtime type
 checks).

Prevayler: http://www.prevayler.org/wiki/

HAppS: http://happs.org (look for the MACID monad)

Prevayler is an efficient and very simple way of providing application state 
persistency. 

Essentially:
- all the state is kept in memory, in native language data structures 
- whenever a write transaction is performed the system automatically 
serialises a description of the transaction so that it can be replayed later.
- occasionally the whole state can be serialised to produce a snapshot
- when the system restarts it reads in the last snapshot and replays all 
transaction since the last snapshot.

Is this orthogonal persistence? 

I guess it would be, if you never took any snapshot. 

Snapshots are limited by what can be serialised in the language.

But transactions might be serialisable even if the state they produce isn't 
(because, say, includes arbitrary functions).

Best,

  titto


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


[Haskell-cafe] Reification in Haskell, was: To yi or not to yi

2007-06-20 Thread Pasqualino 'Titto' Assini
Hi everybody,

What is the situation with respect to reification of function/thunks in 
Haskell?

Does any current implementation support it ? 

And, is there any plan for GHC to support it?

Claus's comments on this, follow.

 titto


On Monday 18 June 2007 23:45:23 Claus Reinke wrote:
  Is there any fundamental reasons why Haskell functions/closures
  cannot be serialised?

 no, and that is part of the problem: the language would need to be
 extended, but the academically interesting issues have been tackled,
 all that is left is a lot of work (that is why these things would be so
 valuable: complex implementation machinery, controlled by very
 small language extensions, sometimes even language simplifications,
 such as lifting existing restrictions on i/o), preferably with very good
 planning, so that all the work does not become useless right after it
 is finished. there isn't much hope that this issue is going to be settled
 via the usual academic funding sources.


  Most languages, even Java, have a reflection capability to dynamically
  inspect an object. It is surprising that Haskell doesn't offer it.

 it has to be done with care, or it will invalidate *all* your nice
 reasoning about haskell programs. random example

 reify (f . g) == [| f . g |] =/= [| \x- f (g x) |] == reify (\x- f (g
 x))

 reification is not a referentially transparent program context.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Collections

2007-06-20 Thread apfelmus
Thomas Conway wrote:
 In particular, I find my self wanting to use a priority queue for
 N-way sorted merge, which you can do with Data.Map: (compiles, so
 clearly works even though I have not tested it. ;-) )
 
 import Data.List as List
 import Data.Map as Map
 
 merge :: Ord t = [[t]] - [t]
 merge lists = merge' $ Map.fromList $ concatMap makePair lists
where
makePair [] = []
makePair (x:xs) = [(x,xs)]
 
 merge' heap
| Map.null heap = []
| otherwise = x:(merge' $ removeEqual x $ reinsert xs heap')
where
((x,xs), heap') = deleteFindMin heap
 
 reinsert [] heap = heap
 reinsert (x:xs) heap = Map.insert x xs heap
 
 removeEqual x heap
| Map.null heap = heap
| x /= y= heap
| otherwise = removeEqual x $ reinsert ys heap'
where
((y,ys), heap') = deleteFindMin heap

Eh, why not a simple mergesort that also deletes duplicates?

-- the nested lists must be sorted: map sort xs == xs
  mergesort :: Ord a = [[a]] - [a]
  mergesort []  = []
  mergesort xs  = foldtree1 merge xs

  foldtree1 :: (a - a - a) - [a] - a
  foldtree1 f [x] = x
  foldtree1 f xs  = foldtree1 f $ pairs xs
 where
 pairs []= []
 pairs [x]   = [x]
 pairs (x:x':xs) = f x x' : pairs xs

  merge :: Ord a = [a] - [a] - [a]
  merge [] ys = ys
  merge xs [] = xs
  merge xs'@(x:xs) ys'@(y:ys)
  | x   y= x:merge xs  ys'
  | x == y=   merge xs  ys'
  | otherwise = y:merge xs' ys

The function 'foldtree1' folds the elements of the list as if they where
in a binary tree:

  foldrtree1 f [1,2,3,4,5,6,7,8]
 ==
  ((1 `f` 2) `f` (3 `f` 4)) `f` ((5 `f` 6) `f` (7 `f` 8))

and with f = merge, this serves as heap (although a very implicit one).
The hole mergesort will take

  O(n*log (length xs)) where n = length (concat xs)

time. Moreover, this variant of mergesort happens to generate elements
as soon as they are available, i.e.

 head . mergesort  is  O(n)

See also

 http://article.gmane.org/gmane.comp.lang.haskell.general/15010


 The other thing I have found myself doing often is using splitLookup
 followed by union, though what I really want is join being the dual
 of split - i.e. requiring all the keys in the rhs to be greater than
 the keys in the lhs. My own AVL tree implementation has this operation
 which is O(log n), which is rather better than union's O(n log n).

2-3-Finger trees support efficient splits and concatenations:

  http://www.soi.city.ac.uk/~ross/papers/FingerTree.html

In fact, you can build a plethora of data structures from them.

Regards,
apfelmus

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


Re: [Haskell-cafe] To yi or not to yi, is this really the question? A plea for a cooperative, ubiquitous, distributed integrated development system.

2007-06-20 Thread Jules Bean

Thomas Schilling wrote:

* Structural (optionally Type-Directed) Editing

Structural editing means that your code is always (mostly) syntactically 
correct, and in case of haskell maybe also type-checked.  This also 
implies that edit operations have syntactic awareness.  paredit[1] 
emulates this quite nicely for lisp, Proxima does something like this in 
Haskell for Haskell and XML-based languages.  This also needs some way 
of incremental parsing, for which good techniques already exist[3].



Paredit doesn't just work for lisp. It works for almost all emacs modes, 
including e.g., haskell and perl (incidentally, I believe it works well 
for XML/SGML type stuff too). I use it regularly for various programming 
languages. Of course, it isn't perfect in a few respects, but it's 
pretty customisable and the author is responsive to ideas and questions.


It's not type-directed, of course. Merely structural. But that alone is 
very handy.


(Incidentally I agree with most of Thomas' points which I snipped, too)

Jules

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


Re: [Haskell-cafe] Perl-style numeric type

2007-06-20 Thread Henning Thielemann

On Tue, 19 Jun 2007, Brent Yorgey wrote:

 But before I get too far (it looks like it will be straightforward yet
 tedious to implement), I thought I would throw the idea out there and see if
 anyone knows of anything similar that has already been done before (a
 cursory search of the wiki didn't turn up anything).  I don't want to
 reinvent the wheel here.

Do you have some examples, where such a data type is really superior to
strong typing? There are examples like computing the average, where a
natural number must be converted to a different type:
  average xs = sum xs / fromIntegral (length xs)
 but this one can easily replaced by
  average xs = sum xs / genericLength xs

 Thus, before you spend much time on making Haskell closer to Perl, how
about collecting such examples, work out ways how to solve them elegantly
in the presence of strong typing and set up a wiki page explaining how to
work with strongly typed numbers? I think, this topic really belongs to
  http://www.haskell.org/haskellwiki/Category:FAQ
 Strongly typed numbers are there for good reason: There is not one type
that can emulate the others. Floating point numbers are imprecise, a/b*b=a
does not hold in general. Rationals are precise but pi and sqrt 2 are not
rational. People have designed languages again and again which ignore
this, and they failed. See e.g. MatLab which emulates an integer (and even
a boolean value) by a complex valued 1x1 matrix.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Avoiding Non-exhaustive patterns in function f

2007-06-20 Thread Henning Thielemann

On Tue, 19 Jun 2007, Stefan O'Rear wrote:

 Like all good UNIX compilers, GHC will only print warnings if you ask it
 to, with -Wincomplete-patterns (iirc).  -Wall enables most of them, the
 full list is in The Glorious Glasgow Haskell Compilation System User's
 Guide (a valuable read!)

Since GHC is not a C compiler (philosophy: the programmers knows what he
does) but a Haskell compiler (philosophy: assist the programmer on
finding mistakes) the warnings should be on by default, to encourage good
programming style and find mistakes early. Non-exhaustive patterns often
indicates possible situations for crashes. unused identifier  often
indicates that one has not completed the implementation of a function.

Unfortunately GHC-6.4 warns about unnecessarily imported modules, but when
you remove the import statement, some identifiers are missing.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Avoiding Non-exhaustive patterns in function f

2007-06-20 Thread Simon Peyton-Jones
| Unfortunately GHC-6.4 warns about unnecessarily imported modules, but when
| you remove the import statement, some identifiers are missing.

If that is still the case with 6.6.1, please do submit a bug report and 
example.  Thanks!

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


Re: [Haskell-cafe] Perl-style numeric type

2007-06-20 Thread Brent Yorgey

On 6/20/07, Henning Thielemann [EMAIL PROTECTED] wrote:



Do you have some examples, where such a data type is really superior to
strong typing? There are examples like computing the average, where a
natural number must be converted to a different type:
  average xs = sum xs / fromIntegral (length xs)
but this one can easily replaced by
  average xs = sum xs / genericLength xs

Thus, before you spend much time on making Haskell closer to Perl, how
about collecting such examples, work out ways how to solve them elegantly
in the presence of strong typing and set up a wiki page explaining how to
work with strongly typed numbers? I think, this topic really belongs to
  http://www.haskell.org/haskellwiki/Category:FAQ
Strongly typed numbers are there for good reason: There is not one type
that can emulate the others. Floating point numbers are imprecise, a/b*b=a
does not hold in general. Rationals are precise but pi and sqrt 2 are not
rational. People have designed languages again and again which ignore
this, and they failed. See e.g. MatLab which emulates an integer (and even
a boolean value) by a complex valued 1x1 matrix.



That's a good idea too, perhaps I will do that.  This would be a good thing
to have on the wiki since it's clearly an issue that people learning Haskell
struggle with (I certainly did).  I also want to make clear, though, that I
certainly appreciate the reasons for strongly typed numbers.  I am not
trying to make Haskell closer to Perl in general (God forbid!), or in any
way advocate for doing away with strongly typed numbers, but only to create
a library for working more conveniently with numeric types in small programs
where the typing is not as important.  To give a couple quick examples,
based on what I have already implemented:

*EasyNum 1 / 3
0.
*EasyNum 1 / 3 :: EasyNum
1/3
*EasyNum 1 / floor pi

interactive:1:4:
   Ambiguous type variable `t' in the constraints:
 `Integral t' arising from use of `floor' at interactive:1:4-11
 `Fractional t' arising from use of `/' at interactive:1:0-11
   Probable fix: add a type signature that fixes these type variable(s)
*EasyNum 1 / floor pi :: EasyNum
1/3

I would have also put in the example of 1 / pi :: EasyNum and show it
printing out a double value instead of the rational it prints with 1 / 3,
except I haven't yet implemented the instance of Floating. =)

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


Re: [Haskell-cafe] Perl-style numeric type

2007-06-20 Thread Henning Thielemann

On Wed, 20 Jun 2007, Brent Yorgey wrote:

 That's a good idea too, perhaps I will do that.  This would be a good thing
 to have on the wiki since it's clearly an issue that people learning Haskell
 struggle with (I certainly did).  I also want to make clear, though, that I
 certainly appreciate the reasons for strongly typed numbers.  I am not
 trying to make Haskell closer to Perl in general (God forbid!), or in any
 way advocate for doing away with strongly typed numbers, but only to create
 a library for working more conveniently with numeric types in small programs
 where the typing is not as important.  To give a couple quick examples,
 based on what I have already implemented:

 *EasyNum 1 / 3
 0.
 *EasyNum 1 / 3 :: EasyNum
 1/3
 *EasyNum 1 / floor pi

 interactive:1:4:
 Ambiguous type variable `t' in the constraints:
   `Integral t' arising from use of `floor' at interactive:1:4-11
   `Fractional t' arising from use of `/' at interactive:1:0-11
 Probable fix: add a type signature that fixes these type variable(s)
 *EasyNum 1 / floor pi :: EasyNum
 1/3

How about
 1 % floor pi

?

Already two examples for the Wiki which I used to start the Wiki article:
  http://www.haskell.org/haskellwiki/Generic_numeric_type
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] csv library

2007-06-20 Thread Jaap Weel
This is an announcement of something so tiny (about 100 lines of code
including comments), I'd feel bad posting it to the haskell list, so
it'll go on haskell-cafe. This was pretty much just a project for me
to learn cabal and hackage, but it may very well actually come in
useful some day.

  csv 0.1.0
CSV loader and dumper

 This library parses and dumps documents that are formatted according
 to RFC 4180, The common Format and MIME Type for Comma-Separated
 Values (CSV) Files. This format is used, among many other things, as
 a lingua franca for spreadsheets and for certain web services.

 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/csv-0.1.0

--  


   /jaap





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


Re: [Haskell-cafe] Collections

2007-06-20 Thread Jens Fisseler
On Tue, 19 Jun 2007, Andrew Coppin wrote:

 Maybe it's just a culture thing then... In your typical OOP language, you
 spend five minutes thinking now, what collection type shall I use here?
 before going on to actually write the code. In Haskell, you just go OK, so
 I'll put a list here...

I seriously doubt this.

You kind of mix two things, languages and libraries. Collections will most 
of the time be implemented as a library.

So, in order to use the appropriate collection type, you have to know 
you're standard library or know of other libraries available. Then, 
whenever you need an appropriate collection type, you look what's 
available. It's this way with Java, with C++ and *definitely* with 
Haskell, too.

Regards,

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


Re: [Haskell-cafe] Reading/writing packed bytes from file

2007-06-20 Thread Jefferson Heard
What about the Data.Binary module from the Hackage database?  I can call
C, no problem, but I hate to do something that's already been done.

On Wed, 2007-06-20 at 12:02 +1000, Donald Bruce Stewart wrote:
 jeff:
  I've read the documentation for some of the marshalling packages out
  there for Haskell, and I'm left confused as to which one I should be
  using and how to actually do what I want to do.   I have a file, a
  little over 2gb, of packed data in the format
  
  (recordcount) records of:
  
  4-byte int (count),
  (count) 2-byte unsigned shorts,
  (count) 4-byte floats
  
  all in little-endian order.  What I want to do is read each record
  (lazily), and unpack it into Data.IntMap.IntMap Float where the unsigned
  shorts become the keys and the 4-byte floats become the values.
  
  Then I want to do a lot of interesting processing which we'll skip here,
  and write back out packed data to a file in the format of
  
  4-byte float,
  4-byte float,
  4-byte float
  
  for each record. I need these output records to be four-byte C floats.
  I've gotten as far as datatypes and a couple of signatures, but I can't
  figure out the functions themselves that go with the signatures, and
  then again, maybe I have the signatures wrong.  
  
  -- 
  import qualified Data.IntMap as M
  import qualified Data.ByteString.Lazy.Char8 as B
  
  data InputRecord = M.IntMap Float
  data OutputRecord = (Float, Float, Float)
  
  -- open a file as a lazy ByteString and break up the individual records
  -- by reading the count variable, reading that many bytes times 
  -- sizeof short + sizeof float into a lazy ByteString.
  readRawRecordsFromFile :: String - IO [B.ByteString] 
  
  
  -- take a bytestring as returned by readRawRecordsFromFile and turn it
  -- into a map.
  decodeRawRecord :: B.ByteString - M.IntMap Float
  --
  
  Can anyone help with how to construct these functions?  I'm going to
  have to make a few passes over this file, so I'd like the IO to be as
  fast as Haskelly possible.
  
  -- Jeff
 
 Data.ByteString.Lazy.Char8.readFile should suffice for the IO.
 then use drop/take to split up the file in pieces if you know the length
 of each field.
 
 For converting ByteString chunks to Floats, I'd probably call C for that.
 
 -- Don

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


Re: [Haskell-cafe] Reading/writing packed bytes from file

2007-06-20 Thread Bulat Ziganshin
Hello Jefferson,

Wednesday, June 20, 2007, 12:20:28 AM, you wrote:

 4-byte int (count),
 (count) 2-byte unsigned shorts,
 (count) 4-byte floats

using my Streams package ( http://haskell.org/haskellwiki/Library/AltBinary ):

import Data.AltBinary
readall recordcount h = do
  replicateM recordcount $ do
count - getWord32le h
keys   - replicateM count (getWord16le h :: IO Int)
values - replicateM count (getFloat h)
return (IntMap.fromList (zip keys values))

This isn't lazy and not tested

 all in little-endian order.  What I want to do is read each record
 (lazily), and unpack it into Data.IntMap.IntMap Float where the unsigned
 shorts become the keys and the 4-byte floats become the values.

 Then I want to do a lot of interesting processing which we'll skip here,
 and write back out packed data to a file in the format of

 4-byte float,
 4-byte float,
 4-byte float

 for each record.

use either putFloat or define structure of 3 floats:

data F = F Float Float Float

and put entire F to the stream:

mapM_ put_ (IntMap.values your_map)




-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Can't build Lambdabot

2007-06-20 Thread Daniel Fischer
Okay,  if lambdabot isn't as cool as I believe, it's definitely not worth the 
fuss. Although, it comes with hoogle and djinn, which are quite neat.

Am Dienstag, 19. Juni 2007 00:41 schrieb Stefan O'Rear:

 Your lambdabot is too old.  It needed fixes to work with GHC 6.6's
 version of the haskell-src package.

 Stefan

Complaint: then why is it in Hackage? 
I got it from there only monday, if it's obsolete (won't work with ghc 
later than 6.4.x), please mark it so or remove it.
I darcs got lambdabot yesterday (I have no DSL, so it took over 30 minutes, 
that's why I prefer .tar.* versions), it's still tagged 4.0, that makes me a 
little uneasy, but I'll see.
So now I also need zlib, binary=2.0 and arrows.
Okay, got 'em.
Next complaint: the building instructions aren't good enough for dummies like 
me.

What changes to make to Config.hs?
The fortunePath is explained well, but
What should the fptoolsPath be?
Or, what should be in the directory it points to?
Somebody please tell me.
And what's the outputDir for?
Should I change it or not?

One more:

Note: If you want lambdabot to be able to evaluate expressions
(e.g.,  1 + 1 evaluates to 2) then you'll need hs-plugins and also
before './Setup.hs configure --bindir=`pwd`' you need to copy
lambdabot.cabal.plugins to lambdabot.cabal.

I have the impression that I need plugins anyway, and lambdabot.cabal.plugins 
seems to be pre-6.6, lists fps=0.7 among the Build-Depends, but not zlib, 
binary=0.2, arrows, regex-compat, regex-posix, and would try to build 
lambdabot-dynamic, apparently, which in the comment above is dubbed 'Not 
quite there yet'. Suspicious.

So I did a bit of guessing and started the build.
Build failed compiling Parser.hs: not in scope as_name c.
In the new Parser.hs, there is

#if __GLASGOW_HASKELL__  606
as_name = HsIdent as
hiding_name = HsIdent hiding
qualified_name = HsIdent qualified
minus_name = HsSymbol -
pling_name = HsSymbol !
#endif

Hrm, I have ghc 6.6.1, that seems to define __GLASGOW_HASKELL__ as 606,
so I changed '' to '=', hoping for the best.
Then evereything built fine until...
compiling ShowQ.hs. Two instances Arbitrary (Maybe a), one there, one in 
Test.QuickCheck.
Okay, the only way round that which I could see, was commenting out the 
offending instance in ShowQ.
Then no more build failures, unfortunately:
$ ./lambdabot
Initialising plugins Speicherzugriffsfehler

I haven't even the foggiest what might be causing that.
If it were the fact that my fptools directory is empty, I'd expect a better 
message.

Now what I need is to figure out how to get lambdabot going at all and how to 
use ft, runplugs, smallcheck  quickcheck (djinn and hoogle provide 
information on how to use them, the others don't).

It would be much appreciated if at least pointers to such information were 
included in the README. Even more if someone could correctly guess what's 
wrong with my bot.

Cheers,
Daniel

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


Re: [Haskell-cafe] Perl-style numeric type

2007-06-20 Thread Brent Yorgey

On 6/20/07, Henning Thielemann [EMAIL PROTECTED] wrote:



How about
1 % floor pi

?

Already two examples for the Wiki which I used to start the Wiki article:
  http://www.haskell.org/haskellwiki/Generic_numeric_type



What about the function isSquare?

isSquare :: (Integral a) = a - Bool
isSquare n = (floor . sqrt $ fromIntegral n) ^ 2 == n

Is there any way to write that without the fromIntegral?  If you leave out
the fromIntegral and the explicit type signature, it type checks, but the
type constraints are such that there are no actual types that you can call
it on.

As I think about it more, I guess one of my biggest goals is essentially to
have an integral type which can silently convert to a rational or floating
type when necessary (e.g. you should be able to call sqrt on an integral
type and have it implicitly convert to floating).  Perhaps this actually has
less to do with scripting-language-style numeric types than it does with
languages (e.g. Java) that do implicit type conversions in directions where
no information is lost -- e.g. you can take the sqrt of an int and get a
double, but if you want to change a double into an int you have to
explicitly truncate or round or whatever.

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


[Haskell-cafe] Re: [Haskell] ANN: Uniplate 1.0

2007-06-20 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Neil Mitchell wrote:
 Hi
 
 Thinking about this slightly further...
 
 For the implementation, Data.Derive has a special case for lists,
 tuples and Maybe. Its a shame that only a restricted number of types
 are supported - things like Data.Map/Data.Set can be supported
 perfectly, apart from restrictions in Template Haskell.
 
 There are two cases.
 
 1) The data structure contains values, in specific places. Lists,
 tuples, Either etc. are all like this. The rules in the paper cover
 all these situations.
 
 2) The data structure contains values, but their place is a feature of
 the data structure - i.e. Map/Set. In this case the right thing to do
 is probably to do fromList/toList pairs on them.

Use Data.Traversable somehow - lots of things are instances of that.
I'm just reading a paper about it...

A similar benefit can be found in the reassembly of a full data
structure from separate shape and contents. This is a stateful
operation, where the state consists of the contents to be inserted; but
it is also a partial operation, because the number of elements provided
may not agree with the number of positions in the shape.
(p.10 http://web.comlab.ox.ac.uk/oucl/work/bruno.oliveira/iteratorJFP.pdf )

That reminded me of the 'uniplate' function... I haven't thought too
closely about this, but it feels right.

Also I wonder, since we can do deriving Functor, and Traversable
instances are equally straightforward according to the paper, should we
have deriving(Traversable)?  Of course this would depend on the order of
the constructor arguments just like deriving Ord, etc, do.


Isaac
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGeUKDHgcxvIWYTTURApT5AKCB1QG4cgMoORIAf65LsyV1DFJc7wCgi2BJ
wpKuYhtPZRriZ1qPzpy1Xe8=
=a8ir
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Perl-style numeric type

2007-06-20 Thread Brent Yorgey

On 6/19/07, Brent Yorgey [EMAIL PROTECTED] wrote:


I've started developing a library to support a Perl-style numeric type
that does the right thing without having to worry too much about types...



So, I just completed my implementation and decided to test it out by
converting a simple program I wrote the other day (which exhibited lots of
fromIntegers and such) to use my generic number type.  When I was done
converting, the code looked much simpler, which was nice.  It type-checked
and compiled just fine.  And... didn't work.  After a number of minutes of
fiddling around, I finally realized that something which I knew was an
integer was actually being represented as a Double internally due to some
operator I had used previously, which was causing the isSquare function to
always return False (equality of floating-point numbers and all that =P ).
Adding a call to round fixed it, BUT I sheepishly realized that yes, I had
just spent five minutes tracking down a bug that the type checker would have
found for me had I not worked so hard to do stuff behind its back.

Consider me chastened!  *goes off to contribute to that wiki page that
Henning started...*

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


Re: [Haskell-cafe] Reification in Haskell, was: To yi or not to yi

2007-06-20 Thread Bulat Ziganshin
Hello Pasqualino,

Wednesday, June 20, 2007, 11:30:32 AM, you wrote:

  Most languages, even Java, have a reflection capability to dynamically
  inspect an object. It is surprising that Haskell doesn't offer it.

how about asm? :)  there are no OOP objects in Haskell, each name is
just an address of memory area. all operations are checked statically
(at compile time). reflection capabilities may be only handmade - you
can get any type info via hidden class dictionary (see
http://homepages.inf.ed.ac.uk/wadler/papers/class/class.ps.gz for
details of type classes implementation)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Re: Orthogonal Persistence in Haskell

2007-06-20 Thread Claus Reinke
Prevayler is an efficient and very simple way of providing application state 
persistency. 


Essentially:
- all the state is kept in memory, in native language data structures 
- whenever a write transaction is performed the system automatically 
serialises a description of the transaction so that it can be replayed later.

- occasionally the whole state can be serialised to produce a snapshot
- when the system restarts it reads in the last snapshot and replays all 
transaction since the last snapshot.


thanks for the explanation. but this means that there is one process
permanently running and holding on to all the application state in main
memory. if you want to shut down, move, or replicate that process,
you need to get hold of its data, and if you can't communicate its
data to worker processes, you have to communicate the work into
the repository process. all limited by serialisation, unless that aspect
is kept implicit by accross-the-board support for persistence and
first-class communications.

its a bit like pointers in haskell: just about everything a haskell program
touches is a pointer (unboxing or shared constants are optimisations),
but usually, haskell programs talk about the data being referenced, 
not about the references. if you want to share or forget the data,

you move the references, and the system handles memory management
behind the scenes.

with orthogonal persistence, everything a program touches might 
persist, but usually, programs talk about the data being persistet (?),
not about whether that data is currently temporary or in long-term 
storage. if you want to move such data between processes or storage 
areas, you move the reference, and the system handles serialisation/

communication/deserialisation behind the scenes.

Is this orthogonal persistence? 


it doesn't seem so. but it does try to address the same issues, in an
environment limited by its lack of support for orthogonal persistence.

i used to have a long list of references to the area here:

http://www.cs.kent.ac.uk/people/staff/cr3/bib/bookshelf/Persistence.html

which might still give some overview of titles, but note that almost all 
of the urls are out-of-date or have disappeared entirely. 

lets see whether i can find some of them again: St.Andrews seems to 
have preserved some of its older groups' information, including publication 
lists (some of the publications are online as well):


http://www-old.cs.st-andrews.ac.uk/research/publications.php?keyword=persistence
http://www-old.cs.st-andrews.ac.uk/research/publications.php?keyword=reflection

and has a wiki, too:

http://www-systems.cs.st-andrews.ac.uk/wiki/Persistence
http://www-systems.cs.st-andrews.ac.uk/wiki/Linguistic_Reflection

and there were some survey papers, including:

   Orthogonally Persistent Object Systems (1995) 
   Malcolm Atkinson, Ronald Morrison; VLDB Journal


   http://citeseer.ist.psu.edu/atkinson95orthogonally.html

many of the topics talked about in those papers will be more familiar
to todays haskellers than to the general programming language audience
of the time (first class procedures, type abstraction, existentials, runtime
code generation, ...). but note that most of the material is old, so code
might be in terms of algol variants, not haskell, compile-time reflection,
not template haskell, runtime reflection, not meta-ml, reflection where
generic programming would be sufficient, and so on..

and todays haskellers are certainly aware of the issues addressed in
that old work on unifying database and programming language research:
getting the advantages of databases into production code without the 
hassle of dealing with two separate and incompatible semantics and 
systems. instead of seeing databases as external to programming

languages, they become integrated structures/features of the language.

hth,
claus

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


Re: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-20 Thread Bulat Ziganshin
Hello Anatoly,

if you still believe in haskell/ghc speed i suggest you to read the
following:
http://www.cse.unsw.edu.au/~chak/papers/afp-arrays.ps.gz
http://www.cse.unsw.edu.au/~dons/papers/fusion.pdf


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


RE: [Haskell-cafe] Haskell mode for emacs - some questions

2007-06-20 Thread peterv
Yes, HopenGL works fine using GHCI, Gtk2HS/SOE doesn't (it already explained
in somewhere this mailing list)

For particle systems, the interpreted overhead will be large I guess. At
least for the L-System I tested, compiling with GHC resulted in much much
faster execution.

-Original Message-
From: Jules Bean [mailto:[EMAIL PROTECTED] 
Sent: Tuesday, June 19, 2007 09:58
To: peterv
Cc: 'David House'; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Haskell mode for emacs - some questions

peterv wrote:
 And when I will me using HopenGL, I will want performance, as I will be
 doing experiments with particle systems, 3D rendering, etc. Basically the
 stuff I did for many years but now using Haskell :)
 
 Having to do anything more than hitting a key to compile and run an
 application would simple be unacceptable from the point of view of an
imp/OO
 developer (all imp/OO IDEs have that). Furthermore, when programming
 videogames or special effects, you have to run and test a lot, because
what
 you see on screen usually 
 determines your next actions. 

I don't disagree that this should be possible. If you hit C-h f compile 
then you can read the documentation for the built-in compile command. By 
default this runs make, because many code projects especially in the 
unix world use make as their build system, but you can customise this.

On the other hand a simple haskell project doesn't have any way of 
indicating which is the 'main' file (indeed most of my haskell projects 
with more than one file have more than one 'main' file with different 
purposes) so it's not immediately obvious which arguments to give to ghc 
--make.  I suspect that this itch is just not sufficiently important to 
most haskell-mode users, since the alternatives (C-c C-l, C-x b M-p 
RET, or alt-tab up ret) [*] work so well.

Incidentally I've developed using HOpenGL in ghci with no problem. The 
performance is not really an issue: only the 'current file' is 
interpreted, all other files are used compiled, and in any case most of 
the CPU usage is in the (compiled) GL libraries of your system.

Jules

* C-x b M-p RET being 'switch to your shell buffer, select previous 
command and re-run it', since your previous command is obviously ghc 
--make foo.hs  ./foo.  Alt-tab up ret is the same thing except it 
switches to a non-emacs shell window using your window manager, if you 
don't like using emacs shells :)


No virus found in this incoming message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.1/854 - Release Date: 19/06/2007
13:12
 

No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.1/854 - Release Date: 19/06/2007
13:12
 

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


RE: [Haskell-cafe] Re: Haskell mode for emacs - some questions

2007-06-20 Thread peterv
 Sounds like it was difficult.  Could you describe what you tried

Actually, it was easy once I switched from xemacs to emacs... Of course, I 
missed the part in the wiki that xemacs does not work without some changes, mea 
culpa. The reason I used xemacs was because the previous version of emacs did 
not support good font smoothing (cleartype) on Windows, but that seems to be 
fixed now. Also, I just found out about the EmacsW32 package which is really 
easy to install on Windows. 

 currently Emacs doesn't know which file is the main one

So emacs has no concept of a startup project and a solution or workspace 
like Visual Studio and Eclipse? Well yes, that explains why this feature is 
missing. I guess I can just as will stick to typing run as the compile 
command and creating a run batch file...

 In VS or Eclipse, what do you have to do in order for F5 to work?

In VS you have a solution which is a set of projects. A project is 
basically a module, which can be an executable or library. The user marks one 
or more executable projects as startup projects. When hitting F5, all the 
dirty dependent projects are compiled and linked, and all the startup 
projects are run. Usually you just have a single startup project. 

 We could also add a binding which sends main to GHCi.

Would be nice. But I'll still have to use GHC a lot for performance.

 I use this hack all the time and haven't been bitten yet.  

Super! Then it's worth for me to figure out how that works. 

Thanks a lot,
Peter

-Original Message-
From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Stefan Monnier
Sent: Tuesday, June 19, 2007 20:52
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] Re: Haskell mode for emacs - some questions

 I finally got emacs using Haskell-mode working. It seems that the latest

Sounds like it was difficult.  Could you describe what you tried, what
didn't work, and what did work in the end?  Hopefully I can then improve
the doc.

 - How can I just compile and run in one go without having to type ghc
 --make main.hs as arguments for the compile... command and then typing
 main.exe for shell command...? This is what you do all the time when
 using Visual Studio, Eclipse, etc: just hit the F5 key which builds all the
 dependencies and runs one or more generated executables. Easy. Visual
 Haskell does this (in the cases it does not hang for some unknown reason).
 Of course I could dig into ELISP, but somehow I feel this must be supported
 somehow.

I never use GHC in this way, I always use GHCi instead.  Furthermore, I tend
to work on only parts of a program, so there isn't necessarily
a main function.  I'd be happy to add support for your usage pattern, but
since I'm not familiar with it, I'm not sure what to add.
Another problem is that unless your project is tiny, it'll have several
files and currently Emacs doesn't know which file is the main one.  I added
very-preliminary support for Cabal in the CVS code of haskell-mode which
should allow haskell-mode (at some point in the future) to figure out what's
the main file an how to compile it.
Currently all it does (other than font-lock the cabal file itself) is look
for the Cabal file to figure out the root of the project, so that C-c C-l
first does a cd to the root, which should allow dependencies in other
directories to work more seemlessly.

Patches (or precise feature requests) are very welcome.  E.g. it should be
fairly easy to add an F5 binding like you describe.  The main issue is how
to inform Emacs of what should be done.  In VS or Eclipse, what do you have
to do in order for F5 to work?  Is opening some random source file enough,
or do you have to select a Cabal file or what?

 Use C-c C-l to load the file into GHCi. This is better than just compiling
 it: you get an interactive environment in which to play around with, test
 out functions, etc. You can still 'run' your program by typing 'main'
 in GHCi.

We could also add a binding which sends main to GHCi.

 - There seems to be support for Haskell Font Lock Symbols, which should
 convert \, - and maybe other symbols to good looking Unicode fonts.
 I can't get the correct fonts working on Windows.

I never use Windows so I can't really help you there.  Maybe ask on
gnu.emacs.help how to get those chars displayed.  I'm pretty sure Windows
has the needed fonts, so all that's missing is some way to help Emacs make
use of them.
If you figure it out, please send me a note about what you had to do, so
I can add it to the documentation.  

 Now as I understood this is not really supported because of indentation
 problems, as underneed the single Unicode arrow character is converted
 into -?

You slightly misunderstood: this hack is fully supported.  I just added some
warnings to the docstring to make sure the user doesn't blame me when he
gets bitten.

 This is unfortunate, because that's one of the things I really
 like about Sun's Fortress: the usage of Unicode symbols makes the text
 

RE: [Haskell-cafe] Avoiding Non-exhaustive patterns in function f

2007-06-20 Thread peterv
Super! Would be nice if this gets build into GHC/GHCI :)

-Original Message-
From: Neil Mitchell [mailto:[EMAIL PROTECTED] 
Sent: Wednesday, June 20, 2007 01:07
To: Felipe Almeida Lessa
Cc: peterv; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Avoiding Non-exhaustive patterns in function f

Hi

  I understand this has nothing to do with type checking, but why can't
the
  compiler give a warning about this? Or is this by design or because it
is
  impossible to check with more complex recursive data types?

 Take a look at Catch from Neil Mitchell:
 http://www-users.cs.york.ac.uk/~ndm/catch/ .

Using the released version of Catch on the example you gave:

Analysing
Checking [1/1]: Main: Pattern match failure in function at 5:1-5:10.
Partial: Main.f
Partial: Main.main
Partial: main
Answer: 0

This says: the error message you will get is about a pattern match on
line 5 (that's where 'f' is in the example program). The list of
partial functions, in some kind of call-stack order, is Main.f, then
Main.main - i.e. your main function calls f which is partial. Answer 0
means the necessary precondition for safety is false - or its not
safe at all.

If you turn on logging Catch will additionally tell you that the
precondition on 'f' is that the data structure must be a 'A'
constructed value.

Thanks

Neil

No virus found in this incoming message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.1/854 - Release Date: 19/06/2007
13:12
 

No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.1/854 - Release Date: 19/06/2007
13:12
 

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


RE: [Haskell-cafe] Useful IDE features -

2007-06-20 Thread peterv
 (which just states that record type and field label type together uniquely
determine the field value type)

That's nice. When will a new Haskell standard become official? It seems so
many new extensions exist, that one cannot judge the language by looking at
Haskell98 anymore.

 in practice, overloading introduces overhead that might hamper
performance.

You mean overloading in general, so using type classes? Is this comparable
to the Java/C#/C++ overhead with virtual methods, so one extra level of
indirection before the function gets called? Or is it much worse?

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Claus Reinke
Sent: Wednesday, June 20, 2007 01:28
To: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Useful IDE features - 

 That looks nice, just unfortunate you need to cast to ::Float in
homer2?Age::Float. I don't see 
 why this is needed, but I must say I don't understand your code completely
yet, working on that :)

that annotation is not needed if you keep the functional dependency
(which just states that record type and field label type together uniquely
 determine the field value type)

class Has field value record | field record - value where
(?)  :: record - field - value
(:) :: (field,value) - record - record

 Also, wouldn't this approach be less performant? Or is GHC that good that
ist compiles away all 
 the overhead?

in principle, there is no need for this to be less performant.
in practice, overloading introduces overhead that might hamper
performance.

claus

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

No virus found in this incoming message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.1/854 - Release Date: 19/06/2007
13:12
 

No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.472 / Virus Database: 269.9.1/854 - Release Date: 19/06/2007
13:12
 

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


[Haskell-cafe] RE: [darcs-devel] advice on GADT type witnesses needed

2007-06-20 Thread Simon Peyton-Jones
I've improved the error message for this case. It was indeed bizarrely 
confusing.

Simon

| -Original Message-
| From: Ian Lynagh [mailto:[EMAIL PROTECTED]
| Sent: 15 June 2007 15:53
| To: Jason Dagit
| Cc: haskell-cafe@haskell.org; [EMAIL PROTECTED]; Simon Peyton-Jones
| Subject: Re: [darcs-devel] advice on GADT type witnesses needed
|
| On Thu, Jun 14, 2007 at 08:27:36PM -0700, Jason Dagit wrote:
|  On 6/14/07, David Roundy [EMAIL PROTECTED] wrote:
| 
|  src/Darcs/Patch/Show.lhs:50:0:
|  Quantified type variable `y' is unified with another quantified type
|  variable `x'
|  When trying to generalise the type inferred for `showPatch'
|Signature type: forall x y. Patch x y - Doc
|Type to generalise: Patch y y - Doc
|  In the type signature for `showPatch'
|  When generalising the type(s) for showPatch, showComP, showSplit,
|showConflicted, showNamed
|  make: *** [src/Darcs/Patch/Show.o] Error 1
|  
|  The relevant code is
|  
|  showPatch :: Patch C(x,y) - Doc
|  showPatch (FP f AddFile) = showAddFile f
|  ...
|  showPatch (Conflicted p ps) = showConflicted p ps
|  
|  and the trouble comes about because of (in Core.lhs)
|  
|  data Patch C(x,y) where
|  NamedP :: !PatchInfo - ![PatchInfo] - !(Patch C(x,y)) - Patch C(x,y)
|  ...
|  Conflicted :: Patch C(a,b) - FL Patch C(b,c) - Patch C(c,c)
|  
| 
|  I would like to add that I've tried (and failed) to construct a
|  minimal example that demonstrates the type check failure by simulating
|  the relevant code above.  This makes me wonder if the problem is not
|  in the obvious place(s).
|
| Here's one:
|
| module Q where
|
| data Foo x y where
| Foo :: Foo a b - Foo b c - Foo c c
|
| --
|
| module W where
|
| import Q
|
| wibble :: Foo a b - String
| wibble (Foo x y) = foo x y
|
| foo :: Foo a b - Foo b c - String
| foo x y = wibble x ++ wibble y
|
| 6.6 and 6.6.1 say:
|
| $ ghc -c Q.hs -fglasgow-exts
| $ ghc -c W.hs
|
| W.hs:7:0:
| Quantified type variable `b' is unified with another quantified type 
variable `a'
| When trying to generalise the type inferred for `wibble'
|   Signature type: forall a b. Foo a b - String
|   Type to generalise: Foo b b - String
| In the type signature for `wibble'
| When generalising the type(s) for wibble, foo
| $ ghc -c W.hs -fglasgow-exts
| $
|
| i.e. you need to give the -fglasgow-exts flag when compiling W.hs.
| An {-# OPTIONS_GHC -fglasgow-exts #-} pragma in Show.lhs fixes the real
| thing too.
|
| The HEAD is the same, except the error is:
|
| W.hs:7:8:
| GADT pattern match in non-rigid context for `Foo'
|   Tell GHC HQ if you'd like this to unify the context
| In the pattern: Foo x y
| In the definition of `wibble': wibble (Foo x y) = foo x y
|
| I suspect your problem in making a testcase was moving the GADT
| declaration into the same file as the function, and thus needing to
| compile it with -fglasgow-exts anyway.
|
| I'm not sure if GHC's behaviour is what is expected though; Simon?
|
|
| Thanks
| Ian

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


RE: [Haskell-cafe] Haskell mode for emacs - some questions

2007-06-20 Thread David House
peterv writes:
  Yes, but I can only use GHCI for error checking, because I'm using
  GTK2HS/SOE which does not work well with GHCI under Windows, it only runs
  when using GHC.

Why is this? I'm not that familiar with Gtk2Hs, but I don't understand why it
wouldn't work with GHCi if it works with GHC. They use the same code to compile
it.

On the other hand, you could always just set up a Makefile (which is pretty
trivial) and use M-x compile (which you should bind to a key if you use it a
lot).

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


RE: [Haskell-cafe] Useful IDE features -

2007-06-20 Thread David House
peterv writes:
  That's nice. When will a new Haskell standard become official? It seems so
  many new extensions exist, that one cannot judge the language by looking at
  Haskell98 anymore.

When haskell-prime is ready, which won't be before the MPTC Dilemma [1] gets
resolved, which probably won't be until associated types get fully implemented
in GHC, a new version of GHC gets released and people start to use them.

[1]: 
http://hackage.haskell.org/trac/haskell-prime/wiki/MultiParamTypeClassesDilemma

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


[Haskell-cafe] Re: To yi or not to yi, is this really the question? A plea for a cooperative, ubiquitous, distributed integrated development system.

2007-06-20 Thread apfelmus
Pasqualino 'Titto' Assini wrote:
 Is there any fundamental reasons why Haskell functions/closures cannot be 
 serialised?
 
 I believe that this is precisely what the distributed version of GHC used to 
 do.
 
 Most languages, even Java, have a reflection capability to dynamically 
 inspect 
 an object. It is surprising that Haskell doesn't offer it.

Inspecting functions is not referentially transparent. In Haskell,
function equality is extensional, i.e. two functions are equal when
their results are equal on all arguments. Intensional equality would
mean that functions are equal when they have the same representation. If
you allow a function

 serialize :: (Int - Int) - String

that can give different results on intensionally different functions,
you may not expect equations like

 f (*3) == f (\n - n+n+n)

to hold anymore (because f might inspect its argument). Also, having
serialize somehow check whether intensionally different arguments are
extensionally the same and should have a unique serialization is no
option because this problem is undecidable.

Regards,
apfelmus

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


Re: [Haskell-cafe] Perl-style numeric type

2007-06-20 Thread Henning Thielemann

On Wed, 20 Jun 2007, Brent Yorgey wrote:

 isSquare :: (Integral a) = a - Bool
 isSquare n = (floor . sqrt $ fromIntegral n) ^ 2 == n

 Is there any way to write that without the fromIntegral?  If you leave out
 the fromIntegral and the explicit type signature, it type checks, but the
 type constraints are such that there are no actual types that you can call
 it on.

This is a good example: You wonder, whether fromIntegral can be avoided. I
wonder, whether fromIntegral fulfills the task at all. Actually, it does
not. It fails for big integers, because there is no Double that represents
10^1000. That is you have to rescale the number. Even below this number,
'isSquare' will fail due to rounding errors:

Prelude isSquare ((10^100)^2)
False

 That is, 'isSquare' does not do what it promises.

Btw. I would at least use 'round' because the Double sqrt might be
slightly below the true root.

Unfortunately we don't have access to the native sqrt implementation of
the GNU multiprecision library GMP so we have to roll our own version:

(^!) :: Num a = a - Int - a
(^!) x n = x^n

{- |
Compute the floor of the square root of an Integer.
-}
squareRoot :: Integer - Integer
squareRoot 0 = 0
squareRoot 1 = 1
squareRoot n =
   let twopows = iterate (^!2) 2
   (lowerRoot, lowerN) =
  last $ takeWhile ((n=) . snd) $ zip (1:twopows) twopows
   newtonStep x = div (x + div n x) 2
   iters = iterate newtonStep (squareRoot (div n lowerN) * lowerRoot)
   isRoot r  =  r^!2 = n  n  (r+1)^!2
   in  head $ dropWhile (not . isRoot) iters



Btw. I think that 'squareRoot' is the basic problem and I'd like to change
the Wiki article accordingly.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Plugin Problem

2007-06-20 Thread Daniel Fischer
Hi again,

I thought, I'd try out the plugins package, cause lambdabot segfaulted while 
loading plugins (or immediately after).
So I wrote a very simpleminded test for eval(_) and unsafeEval(_) from 
System.Eval.Haskell.
Compiled, but:
[EMAIL PROTECTED]:~/Documents ghc --make PlugTest
[1 of 1] Compiling Main ( PlugTest.hs, PlugTest.o )
Linking PlugTest ...
[EMAIL PROTECTED]:~/Documents PlugTest
PlugTest: /tmp/MectNX2619.o: unknown symbol 
`pluginszm1zi0_AltDataziDynamic_toDyn_closure'
PlugTest: user error (resolvedObjs failed.)

What does that tell more knowledgeable persons?

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


Re: [Haskell-cafe] Collections

2007-06-20 Thread Andrew Coppin

David House wrote:

Andrew Coppin writes:
   Data.Graph -- graph type
 
  
  What would you use that for? (And what does it do?)


It's for graphs, in the graph-theory [1] sense.
  


Yes, I realise that. (I'm not a graph theory expert, but I'm aware of 
the subject.) But what kind of thing would you use a general graph for? 
(Rather than some more specific custom data type.)



   Data.Tree -- rose tree type
 
  
  What's a rose tree? (I only know about binary trees. Well, and N-ary 
  trees... but nobody uses those.)


Well, it is said that a rose tree by any other name would be just as N-ary. (I
think they're the same concept :)).
  


LOL! I asked Wikipedia about rose tree and got something quite 
different... ;-)


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


Re[2]: [Haskell-cafe] Collections

2007-06-20 Thread Bulat Ziganshin
Hello Chaddai,

Wednesday, June 20, 2007, 3:14:54 PM, you wrote:

 Well lists are really useful, but I don't think all Haskell
 programmers are like you, in fact I think only the enthusiast newbies
 (like.. you maybe ?) only use lists without asking themselves if there
 is not a data structure better suited to their problem.

in most cases there are just so little amount of data to process that
lists are more than enough. in my 8 KLOC program, i have several uses
of hashtables and one of arrays, the rest implemented via lists


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Collections

2007-06-20 Thread Lennart Augustsson

I don't think the collection type (a,b) is best thought of as a loop.
Neither is a (non-trivial) tree.

On 6/20/07, Andrew Coppin [EMAIL PROTECTED] wrote:


Derek Elkins wrote:
 On Tue, 2007-06-19 at 18:49 -0400, Brandon S. Allbery KF8NH wrote:

 Haskell is, in many ways, a descendant of Lisp.  This does tend to
 lead to lists being *the* collection type, in my experience:  sure,
 others get used, but lists are the ones you see in examples and such.


 Not in my experience.  Certainly lists are used all over the place*, but
 I rarely see them abused.  Also, lists aren't lists in Lisp, they're
 more akin to rose-trees (or going the other way, there are only pairs in
 Lisp).


http://xkcd.com/c224.html

 In practice, almost all Haskell programs use custom defined algebraic
 data types which are usually tree like.  Declaring and using data types
 is easier in Haskell than it is in almost any other language.


True...

 * As others have mentioned, lists represent loops and loops are
 extremely common in programming in general.


Um... surely *every* collection type represents a loop?

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

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


Re: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-20 Thread Andrew Coppin

Donald Bruce Stewart wrote:

Finally, to actually get C speed, use a C md5.


I always feel worried when people say this... It's almost like admitting 
hey, Haskell is beautiful, but it can never be fast. I always find 
myself wanting that statement to be false...


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


Re: [Haskell-cafe] Collections

2007-06-20 Thread Andrew Coppin

Derek Elkins wrote:

On Tue, 2007-06-19 at 18:49 -0400, Brandon S. Allbery KF8NH wrote:
  
Haskell is, in many ways, a descendant of Lisp.  This does tend to  
lead to lists being *the* collection type, in my experience:  sure,  
others get used, but lists are the ones you see in examples and such.



Not in my experience.  Certainly lists are used all over the place*, but
I rarely see them abused.  Also, lists aren't lists in Lisp, they're
more akin to rose-trees (or going the other way, there are only pairs in
Lisp). 
  


http://xkcd.com/c224.html


In practice, almost all Haskell programs use custom defined algebraic
data types which are usually tree like.  Declaring and using data types
is easier in Haskell than it is in almost any other language.
  


True...


* As others have mentioned, lists represent loops and loops are
extremely common in programming in general.
  


Um... surely *every* collection type represents a loop?

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


Re: [Haskell-cafe] Collections

2007-06-20 Thread Nicolas Frisby

Just a couple of examples: many non-trivial program analyses (like
optimizations or type-inference) rely on viewing the AST as a graph.
Graph reduction is an evaluation paradigm, and I'm guessing that a
(specification-oriented) interpreter might use a graph.

On 6/20/07, Andrew Coppin [EMAIL PROTECTED] wrote:

David House wrote:
 Andrew Coppin writes:
Data.Graph -- graph type
   
  
   What would you use that for? (And what does it do?)

 It's for graphs, in the graph-theory [1] sense.


Yes, I realise that. (I'm not a graph theory expert, but I'm aware of
the subject.) But what kind of thing would you use a general graph for?
(Rather than some more specific custom data type.)

Data.Tree -- rose tree type
   
  
   What's a rose tree? (I only know about binary trees. Well, and N-ary
   trees... but nobody uses those.)

 Well, it is said that a rose tree by any other name would be just as N-ary. (I
 think they're the same concept :)).


LOL! I asked Wikipedia about rose tree and got something quite
different... ;-)

___
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] Collections

2007-06-20 Thread Albert Y. C. Lai

Andrew Coppin wrote:
But what kind of thing would you use a general graph for? 
(Rather than some more specific custom data type.)


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


Re: [Haskell-cafe] Collections

2007-06-20 Thread Andrew Coppin

Albert Y. C. Lai wrote:

Andrew Coppin wrote:
But what kind of thing would you use a general graph for? (Rather 
than some more specific custom data type.)


Representing networks.


Yes... graph and network are virtually synonymous. I'm still 
wondering what you'd use a network for in a computer program.


(Unless of course you were writing a network simulator, that is...)

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


Re: [Haskell-cafe] Collections

2007-06-20 Thread Andrew Coppin

Lennart Augustsson wrote:

I don't think the collection type (a,b) is best thought of as a loop.


True. That's a rather special type; I haven't seen anything remotely 
like it in any other language.



Neither is a (non-trivial) tree.


Erm... Depends on your idea of loop I suppose.

A tree represents a recursive loop quite nicely. ;-)


My point of course was that an array is a loop just as much as a list 
is. Same goes for a set. Or even a dictionary (looping over key/value 
pairs), whichever way it's implemented internally.


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


RE: [Haskell-cafe] Haskell mode for emacs - some questions

2007-06-20 Thread peterv
Yes this was also very very confusing for me because I had the same idea
about that. I almost gave up on learning Haskell because of that (I wanted
to practice stuff from the SOE book using the latest versions), until I
suddenly found out that GHC *did* work.

Here's the explanation:

On Fri, 2007-06-15 at 23:15 +0200, [EMAIL PROTECTED] wrote:
 I'm learning Haskell using Paul Hudak's book SOE. 
 
 I'm using GHC 6.6 under Windows XP.
 
 GHC on Windows does not seem to come with HGL (is this correct?), so I 
 used Gtk2HS, which contains a SOE implementation.
 
 I noticed that most programs hang when using GHCI, but they work fine 
 with GHC.

It's not GHCi's fault as such. The reason it does not work well in GHCi at
the moment is a bit technical. The Gtk2Hs SOE implementation currently uses
Haskell threads. Like most GUI toolkits, Gtk+ is single threaded and
requires special attention to use it from multiple OS threads. Currently, by
default, GHC produces executables that use the single-threaded runtime
system, and this works fine with multiple Haskell threads because they get
multiplexed on the same OS thread. GHC can however produce executables that
use the multi-threaded runtime system and ghci.exe itself is such a program.
So when you use SOE with GHCi it's actually using multiple threads to access
Gtk+ an not in a safe way, so it goes wrong in a myriad of ways.

I'll take another look at trying to make the SOE stuff work with the
threaded runtime system by using the primitives Gtk2Hs provides to use
Gtk+ safely from multiple threads.

Duncan

-Original Message-
From: David House [mailto:[EMAIL PROTECTED] 
Sent: Wednesday, June 20, 2007 6:42 PM
To: peterv
Cc: 'David House'; haskell-cafe@haskell.org
Subject: RE: [Haskell-cafe] Haskell mode for emacs - some questions

peterv writes:
  Yes, but I can only use GHCI for error checking, because I'm using
  GTK2HS/SOE which does not work well with GHCI under Windows, it only runs
  when using GHC.

Why is this? I'm not that familiar with Gtk2Hs, but I don't understand why
it
wouldn't work with GHCi if it works with GHC. They use the same code to
compile
it.

On the other hand, you could always just set up a Makefile (which is pretty
trivial) and use M-x compile (which you should bind to a key if you use it a
lot).

-- 
-David House, [EMAIL PROTECTED]
---BeginMessage---
On Fri, 2007-06-15 at 23:15 +0200, [EMAIL PROTECTED] wrote:
 I'm learning Haskell using Paul Hudak's book SOE. 
 
 I'm using GHC 6.6 under Windows XP.
 
 GHC on Windows does not seem to come with HGL (is this correct?), so I
used
 Gtk2HS, which contains a SOE implementation.
 
 I noticed that most programs hang when using GHCI, but they work fine with
 GHC.

It's not GHCi's fault as such. The reason it does not work well in GHCi
at the moment is a bit technical. The Gtk2Hs SOE implementation
currently uses Haskell threads. Like most GUI toolkits, Gtk+ is single
threaded and requires special attention to use it from multiple OS
threads. Currently, by default, GHC produces executables that use the
single-threaded runtime system, and this works fine with multiple
Haskell threads because they get multiplexed on the same OS thread. GHC
can however produce executables that use the multi-threaded runtime
system and ghci.exe itself is such a program. So when you use SOE with
GHCi it's actually using multiple threads to access Gtk+ an not in a
safe way, so it goes wrong in a myriad of ways.

I'll take another look at trying to make the SOE stuff work with the
threaded runtime system by using the primitives Gtk2Hs provides to use
Gtk+ safely from multiple threads.

Duncan

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


[Haskell-cafe] Graphical Haskell

2007-06-20 Thread peterv
In the book Haskell School of Expression, streams are nicely explained
using a graphical flow graph.

This is also done more or less in
http://research.microsoft.com/~simonpj/papers/marktoberdorf/Marktoberdorf.pp
t to explain monads and other concepts.

I would like to create a program that allows you to create such flow graphs,
and then let GHC generate the code and do type inference. 

I found a paper where Haskell is used to create a GUI application with
undo/redo etc for creating graphical Basian networks
(http://www.cs.uu.nl/dazzle/f08-schrage.pdf), so this gave me confidence
that I could it do all in Haskell.

Now, instead of generating Haskell code (which I could do first, would be
easier to debug), I would like to directly create an AST, and use an Haskell
API to communicate with GHC. 

I already found out that GHC indeed has such an API, but how possible is
this idea? Has this been done before? I only found a very old attempt at
this, confusingly also called Visual Haskell, see
http://ptolemy.eecs.berkeley.edu/%7Ejohnr/papers/visual.html, but I can't
find any source code for that project.

I did a similar project in C# that generated C++ code, so I've done it
before, just not in Haskell.

Thanks a lot,
Peter


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


[Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-20 Thread Dominic Steinitz
I'm probably missing something here but writing MD5 (and for that matter
 SHA1) requires bit twiddling operations (Data.Bits) and these aren't
defined for ByteString. For example, SHA1 defines the following function
and it's not clear to me how you'd implement this for ByteString rather
than Word8.

f n x y z
   | n = 19 = (x .. y) .|. ((complement x) .. z)
   | n = 39 = x `xor` y `xor` z
   | n = 59 = (x .. y) .|. (x .. z) .|. (y .. z)
   | n = 79 = x `xor` y `xor` z

I'd love to have blazzingly fast implementations for all the functions
in the crypto library so if anyone feels inclined, any contributions
would be very gratefully accepted. Unfortunately, I don't have the time
to do this myself.

Dominic.

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


Re: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-20 Thread David Roundy
As its name implies, ByteString stores a string of bytes, which are Word8.
It's a replacement for a list, not for Word8.

David

On Wed, Jun 20, 2007 at 09:23:51PM +0100, Dominic Steinitz wrote:
 I'm probably missing something here but writing MD5 (and for that matter
  SHA1) requires bit twiddling operations (Data.Bits) and these aren't
 defined for ByteString. For example, SHA1 defines the following function
 and it's not clear to me how you'd implement this for ByteString rather
 than Word8.
 
 f n x y z
| n = 19 = (x .. y) .|. ((complement x) .. z)
| n = 39 = x `xor` y `xor` z
| n = 59 = (x .. y) .|. (x .. z) .|. (y .. z)
| n = 79 = x `xor` y `xor` z
 
 I'd love to have blazzingly fast implementations for all the functions
 in the crypto library so if anyone feels inclined, any contributions
 would be very gratefully accepted. Unfortunately, I don't have the time
 to do this myself.
 
 Dominic.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: practicality of typeful programming

2007-06-20 Thread Daniil Elovkov

Thank you,
yes, I absolutely didn't question the usefulness of typeful
programming to _some_ degree. What is interesting is where the limits
are. And I have a feeling that they are quite close.

The very idea of how proofs are supplied in typeful Haskell and
dependently typed languages seems to put a serious burden on the
programmer. Epigram authors stated 'pay as you go' (if I remember the
wording right). That's true, but still, (awfully sorry if the
following is rubbish) when I choose to garantee the sortedness of the
list, I introduce quite a bit of stuff to define the appropriate list
type and have to deal with it since then, even if I don't care about
that property in other places. Same with typeful haskell (but not
always, I think).

The fact that structure is mixed with properties seems to put some
limits on both doability and, even more, practilaty of encoding
complex properties.

Oleg, do I remember it right that in your (with Lammel and Schupke)
paper Strongly typed heterogeneous collections you say, that the
given approach only works for statically specified SQL query, I mean
encoded in the Haskell program, not parsed from the untyped input
string? (I've just flipped through it, but failed to find this
place...) Either in case when data schema is statically known, or,
even worse, when it's also dynamic.

Interesting, can all the assertions be proved in that case? Like
correspondence between select field types and resultset record types.


2007/6/16, [EMAIL PROTECTED] [EMAIL PROTECTED]:


Daniil Elovkov wrote:
 I've recently asked some questions here about some little type hackery
 implementing an embedded dsl. But now I wonder if it's worth the
 effort at all...

Yes it is. Typed embedded DSL are quite useful and widely used. For
example, Lava (high-level hardware description language) uses phantom
types to prevent the designer from building meaningless circuits
(e.g., connecting a Bool and an Int wires).
http://citeseer.ist.psu.edu/69503.html

There are other such hardware design languages which profitably use
types (which ought to be popularized more). Using types can decrease
the amount of error checking in the implementation.

I highly recommend the following _very_ good thesis on this
topic:
Morten Rhiger
Higher-Order Program Generation
http://www.brics.dk/DS/01/4/index.html



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


Re: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-20 Thread Jason Dagit

On 6/20/07, Andrew Coppin [EMAIL PROTECTED] wrote:

Donald Bruce Stewart wrote:
 Finally, to actually get C speed, use a C md5.

I always feel worried when people say this... It's almost like admitting
hey, Haskell is beautiful, but it can never be fast. I always find
myself wanting that statement to be false...


I agree with you, but at the same time, if Don says something about
the performance of Haskell I tend to trust him on it.  I find that his
ability to optimize Haskell tends to set the bar.  Otoh, I'd love to
see someone demonstrate otherwise here :)

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


Re: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-20 Thread Derek Elkins
On Wed, 2007-06-20 at 15:23 -0700, Jason Dagit wrote:
 On 6/20/07, Andrew Coppin [EMAIL PROTECTED] wrote:
  Donald Bruce Stewart wrote:
   Finally, to actually get C speed, use a C md5.
 
  I always feel worried when people say this... It's almost like admitting
  hey, Haskell is beautiful, but it can never be fast. I always find
  myself wanting that statement to be false...
 
 I agree with you, but at the same time, if Don says something about
 the performance of Haskell I tend to trust him on it.  I find that his
 ability to optimize Haskell tends to set the bar.  Otoh, I'd love to
 see someone demonstrate otherwise here :)

Well this is something else Don said, 

 I'd suspect a pure haskell md5 over bytestrings would be competitive
 with a C implemetation though. Easier to just call OpenSSL.

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


Re: [Haskell-cafe] Collections

2007-06-20 Thread Thomas Conway

On 6/21/07, Andrew Coppin [EMAIL PROTECTED] wrote:

Lennart Augustsson wrote:
 I don't think the collection type (a,b) is best thought of as a loop.

True. That's a rather special type; I haven't seen anything remotely
like it in any other language.


Is it that special? How is it different to the C++ STL std::pair
template type? I must be missing something.

--
Dr Thomas Conway
[EMAIL PROTECTED]

Silence is the perfectest herald of joy:
I were but little happy, if I could say how much.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-20 Thread Anatoly Yakovenko

I don't think the problem with performance of crypto has anything to
do with unpacking ByteStrings. If I unpack the bytestrings first, then
run the hash, and just time the hash algorithm, i still get 4 seconds
with crypto where the C implementation gives me 0.02 seconds.  Thats
200 times slower in haskell, to me it just seems like a bad
implementation.  You should be able to stay within an order of
magnitude from C with haskell without resorting to weird compiler
tricks.

Anatoly

On 6/20/07, Derek Elkins [EMAIL PROTECTED] wrote:

On Wed, 2007-06-20 at 15:23 -0700, Jason Dagit wrote:
 On 6/20/07, Andrew Coppin [EMAIL PROTECTED] wrote:
  Donald Bruce Stewart wrote:
   Finally, to actually get C speed, use a C md5.
 
  I always feel worried when people say this... It's almost like admitting
  hey, Haskell is beautiful, but it can never be fast. I always find
  myself wanting that statement to be false...

 I agree with you, but at the same time, if Don says something about
 the performance of Haskell I tend to trust him on it.  I find that his
 ability to optimize Haskell tends to set the bar.  Otoh, I'd love to
 see someone demonstrate otherwise here :)

Well this is something else Don said,

 I'd suspect a pure haskell md5 over bytestrings would be competitive
 with a C implemetation though. Easier to just call OpenSSL.

___
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] Useful IDE features -

2007-06-20 Thread Claus Reinke

in practice, overloading introduces overhead that might hamper

performance.

You mean overloading in general, so using type classes? Is this comparable
to the Java/C#/C++ overhead with virtual methods, so one extra level of
indirection before the function gets called? Or is it much worse?


usually, don't worry about it. if a program really is slow, still don't
worry about it, but find out where that program is slow. only if a
program is slow in an area that uses overloading, see:

   http://www.haskell.org/haskellwiki/Performance/Overloading

and even there, the advice is not to avoid overloading, but to make
sure that you use specialised versions of overloaded code (by giving
more specific type annotations or specialize pragmas, or by inlining
overloaded code into usage contexts where its overloading can be
resolved to specific types).

claus

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


Re: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-20 Thread Derek Elkins
On Wed, 2007-06-20 at 16:11 -0700, Anatoly Yakovenko wrote:
 I don't think the problem with performance of crypto has anything to
 do with unpacking ByteStrings. If I unpack the bytestrings first, then
 run the hash, and just time the hash algorithm, i still get 4 seconds
 with crypto where the C implementation gives me 0.02 seconds.  Thats
 200 times slower in haskell, to me it just seems like a bad
 implementation.  You should be able to stay within an order of
 magnitude from C with haskell without resorting to weird compiler
 tricks.

A list of Word8 is -extremely- inefficient.

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


[Haskell-cafe] Re: [darcs-devel] advice on GADT type witnesses needed

2007-06-20 Thread Jason Dagit

On 6/20/07, Simon Peyton-Jones [EMAIL PROTECTED] wrote:

I've improved the error message for this case. It was indeed bizarrely 
confusing.


While we're on the subject of bizarrely confusing error messages :)

I had some code like this:
...
 where
 MergeResult (_:p2') (_:p1' ) (_cp1 :\./:_cp2) = fancy_merge $ p1 :\./: p2

and GHC gave me this error message:
My brain just exploded.
I can't handle pattern bindings for existentially-quantified constructors.

Which is amusing, but it doesn't hint (enough) at the workaround,
which appears to be using 'case' instead of let/where.  Any chance
this could be improved to suggest the user tries switching to a case?

I'm now using this code:
 case fancy_merge $ p1 :\./: p2 of
   MergeResult (_:p2') (_:p1' ) (_cp1 :\./:_cp2)

Which seems to make it further with the type checking (my code is
wrong, but at least now I get a normal error from ghc).

Thanks,
Jason



Simon

| -Original Message-
| From: Ian Lynagh [mailto:[EMAIL PROTECTED]
| Sent: 15 June 2007 15:53
| To: Jason Dagit
| Cc: haskell-cafe@haskell.org; [EMAIL PROTECTED]; Simon Peyton-Jones
| Subject: Re: [darcs-devel] advice on GADT type witnesses needed
|
| On Thu, Jun 14, 2007 at 08:27:36PM -0700, Jason Dagit wrote:
|  On 6/14/07, David Roundy [EMAIL PROTECTED] wrote:
| 
|  src/Darcs/Patch/Show.lhs:50:0:
|  Quantified type variable `y' is unified with another quantified type
|  variable `x'
|  When trying to generalise the type inferred for `showPatch'
|Signature type: forall x y. Patch x y - Doc
|Type to generalise: Patch y y - Doc
|  In the type signature for `showPatch'
|  When generalising the type(s) for showPatch, showComP, showSplit,
|showConflicted, showNamed
|  make: *** [src/Darcs/Patch/Show.o] Error 1
|  
|  The relevant code is
|  
|  showPatch :: Patch C(x,y) - Doc
|  showPatch (FP f AddFile) = showAddFile f
|  ...
|  showPatch (Conflicted p ps) = showConflicted p ps
|  
|  and the trouble comes about because of (in Core.lhs)
|  
|  data Patch C(x,y) where
|  NamedP :: !PatchInfo - ![PatchInfo] - !(Patch C(x,y)) - Patch C(x,y)
|  ...
|  Conflicted :: Patch C(a,b) - FL Patch C(b,c) - Patch C(c,c)
|  
| 
|  I would like to add that I've tried (and failed) to construct a
|  minimal example that demonstrates the type check failure by simulating
|  the relevant code above.  This makes me wonder if the problem is not
|  in the obvious place(s).
|
| Here's one:
|
| module Q where
|
| data Foo x y where
| Foo :: Foo a b - Foo b c - Foo c c
|
| --
|
| module W where
|
| import Q
|
| wibble :: Foo a b - String
| wibble (Foo x y) = foo x y
|
| foo :: Foo a b - Foo b c - String
| foo x y = wibble x ++ wibble y
|
| 6.6 and 6.6.1 say:
|
| $ ghc -c Q.hs -fglasgow-exts
| $ ghc -c W.hs
|
| W.hs:7:0:
| Quantified type variable `b' is unified with another quantified type 
variable `a'
| When trying to generalise the type inferred for `wibble'
|   Signature type: forall a b. Foo a b - String
|   Type to generalise: Foo b b - String
| In the type signature for `wibble'
| When generalising the type(s) for wibble, foo
| $ ghc -c W.hs -fglasgow-exts
| $
|
| i.e. you need to give the -fglasgow-exts flag when compiling W.hs.
| An {-# OPTIONS_GHC -fglasgow-exts #-} pragma in Show.lhs fixes the real
| thing too.
|
| The HEAD is the same, except the error is:
|
| W.hs:7:8:
| GADT pattern match in non-rigid context for `Foo'
|   Tell GHC HQ if you'd like this to unify the context
| In the pattern: Foo x y
| In the definition of `wibble': wibble (Foo x y) = foo x y
|
| I suspect your problem in making a testcase was moving the GADT
| declaration into the same file as the function, and thus needing to
| compile it with -fglasgow-exts anyway.
|
| I'm not sure if GHC's behaviour is what is expected though; Simon?
|
|
| Thanks
| Ian



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


[Haskell-cafe] Re: Plugin Problem

2007-06-20 Thread Daniel Fischer
It half worked in ghci. Only all evals failed. That gave me a lead and after a 
lot of tinkering with the code of plugins-1.0, I found out one major problem.
As of 6.6, ghc calls all interfaces 
interface main:Modulename
and so plugins tries to load main_resource_closure instead of 
Modulename_resource_closure. That of course fails.
Unfortunately, I don't know how to fix it.
I suppose in contrast to the version from HackageDB, which I got myself on 
monday, the darcs version works with ghc = 6.6, or I probably would have 
heard about it. So I'll try to get me that, only where?

And I'm rather annoyed that the stuff from HackageDB tends to be obsolete.
How could we attract people to Haskell, if the downloaded packages just don't 
work?
Cheers,
Daniel

Am Mittwoch, 20. Juni 2007 20:32 schrieb ich:
 Hi again,

 I thought, I'd try out the plugins package, cause lambdabot segfaulted
 while loading plugins (or immediately after).
 So I wrote a very simpleminded test for eval(_) and unsafeEval(_) from
 System.Eval.Haskell.
 Compiled, but:
 [EMAIL PROTECTED]:~/Documents ghc --make PlugTest
 [1 of 1] Compiling Main ( PlugTest.hs, PlugTest.o )
 Linking PlugTest ...
 [EMAIL PROTECTED]:~/Documents PlugTest
 PlugTest: /tmp/MectNX2619.o: unknown symbol
 `pluginszm1zi0_AltDataziDynamic_toDyn_closure'
 PlugTest: user error (resolvedObjs failed.)

 What does that tell more knowledgeable persons?

 Thanks,
 Daniel

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


Re: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-20 Thread David Roundy
On Wed, Jun 20, 2007 at 06:19:35PM -0500, Derek Elkins wrote:
 On Wed, 2007-06-20 at 16:11 -0700, Anatoly Yakovenko wrote:
  I don't think the problem with performance of crypto has anything to
  do with unpacking ByteStrings. If I unpack the bytestrings first, then
  run the hash, and just time the hash algorithm, i still get 4 seconds
  with crypto where the C implementation gives me 0.02 seconds.  Thats
  200 times slower in haskell, to me it just seems like a bad
  implementation.  You should be able to stay within an order of
  magnitude from C with haskell without resorting to weird compiler
  tricks.
 
 A list of Word8 is -extremely- inefficient.

To expand on that terse (but very true) statement, a list of Word8
increases the space usage by a factor of probably around an order of
magnitude (two pointers + 1 byte vs 1 byte), completely destroys your
memory access pattern (which becomes random-access rather than sequential),
and introduces additional nonlocal memory accesses.  One would hope that a
hash function would be moderately close to being memory-limited, so we're
talking about a multiple-order-of-magnitude slowdown.

The main benefit of ByteString isn't weird compiler tricks, it's using a
reasonable data structure for the problem (although the weird compiler
tricks help, too).
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Collections

2007-06-20 Thread Jon Harrop
On Wednesday 20 June 2007 20:04:25 Andrew Coppin wrote:
 Lennart Augustsson wrote:
  I don't think the collection type (a,b) is best thought of as a loop.

 True. That's a rather special type; I haven't seen anything remotely
 like it in any other language.

Are you referring to a 2-tuple/pair?

-- 
Dr Jon D Harrop, Flying Frog Consultancy Ltd.
The OCaml Journal
http://www.ffconsultancy.com/products/ocaml_journal/?e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-20 Thread Stefan O'Rear
On Wed, Jun 20, 2007 at 04:49:55PM -0700, David Roundy wrote:
 To expand on that terse (but very true) statement, a list of Word8
 increases the space usage by a factor of probably around an order of
 magnitude (two pointers + 1 byte vs 1 byte), completely destroys your

Three pointers.


[ INFO PTR (like a tag but not quite) ]
[ PTR to Word8 (these are hashconsed, thankfully) ]
[ PTR to next value   ]

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


Re: [Haskell-cafe] Collections

2007-06-20 Thread Dan Piponi

On 6/20/07, Andrew Coppin [EMAIL PROTECTED] wrote:


Yes... graph and network are virtually synonymous. I'm still
wondering what you'd use a network for in a computer program.


Writing a Haskell compiler. http://en.wikibooks.org/wiki/Haskell/Graph_reduction
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Collections

2007-06-20 Thread Tillmann Rendel

Andrew Coppin wrote:

[...] type (a,b) [...]


That's a rather special type; I haven't seen anything remotely 
like it in any other language.


This type isn't that special in Haskell (apart from being 
syntax-sugared), it could be defined as


  data Pair a b = Pair a b

The equivalent of this definition introduces pairs in other languages, 
too. Consider Java:


public class PairA, B {
  public A fst;
  public B snd;
  public Pair(A fst, B snd) {
this.fst = fst;
this.snd = snd;
  }
}

But there's Lisp, wich doesn't allow custom algebraic data types, but 
instead build all data from pairs. They are called cons cells, and could 
be defined like this in Haskell:


  data Cons = Nil | Cons Cons Cons

In Lisp, pairs are indeed special.


A tree represents a recursive loop quite nicely. ;-)


What's a recursive loop?

My point of course was that an array is a loop just as much as a list 
is. 


No, it isn't. A loop has the following properties:

  (1) you can access only the current value
  (2) you can move only forward by computing some new current value

A (single linked) list has the following properties:

  (1) you can access only the current value
  (2) you can move only forward by following the next pointer

An array has the following properties:

  (1) you can access each value
  (2) you don't need to move around

In a lazy language, following the next pointer triggers computing the 
new value, so loops are similar to lists, but different from arrays.


[...] whichever way it's implemented internally. 


The point is: Some usage of Haskell lists is internally implemented as 
loops. for example this haskell code


  let result = 1 : zipWith (+) result result in result !! 10

is equivalent to this c code

  int result = 1;
  for (int i = 0; i  10; i++)
result = result + result;

and is hopefully compiled to something like this c code.


Of course, you can loop over most collections, in the sense of 
repeatedly running some code for each element. This is expressed in 
Haskell in a bunch of type classes, most notably Functor.



Same goes for a set. Or even a dictionary (looping over key/value
pairs), whichever way it's implemented internally.


I take your wichever way to apply to all collections you mentioned. 
Let's consider this set representation:


  type Set a = a - Bool

  dual a x = not (a x)
  member y a = a y
  notMember y a = dual a y
  empty y = False
  insert x a y = x == y || a y
  remove a x y = x /= y  a y
  union a b y = a y || b y
  intersection a b y = a y  b y
  difference a b = intersection a (dual b)
  filter = intersection

(Function names and their meaning is taken from Data.Set. a and b stands 
for sets, x and y for set elements and f for some function. the dual set 
is the set containing all elements except those in the original set)


What has a set represented like this in common with a loop?

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


[Haskell-cafe] Using Template Haskell to automate QuickCheck testing?

2007-06-20 Thread Brent Yorgey

(I originally tried to send this on Jun 8, but it seems that due to various
issues it did not actually get sent over the list.  Apologies if anyone gets
multiple copies.)

Hi all,

Following some recent discussions in #haskell, I've decided to try my
hand at a module to allow automation of QuickCheck testing.  I'm
aware that there are already various homegrown solutions out there,
(e.g. [1],[2]) as well as idiomatic boilerplate to do this (e.g. [3]),
but it feels like there ought to be a more elegant/DRY-style solution.

In my ideal vision, you'd be able to do something like this:

import ModuleToBeTested
import Test.AutoQuickCheck   -- the library module I want to write

prop_foo = blah   -- some QuickCheck tests
prop_bar = blah blah

main = $(runChecks)

...where runChecks would use TH to reflect on the current module, find
any top-level function declarations beginning with prop_, and
generate code to run them all through QuickCheck, printing the
results.  I think the attractions of such a system (if it could
actually work) should be obvious.

However, after reading all about TH it doesn't seem like there's a way
to do this (reflecting on the current module to pull out the names of
certain top-level declarations).  Since I don't know much about how TH
is implemented, I'm not sure whether (1) there's a good reason this is
pretty much impossible with TH; (2) it would be possible but it's
currently unimplemented; or (3) there actually is a way to do what I
want, but I'm not clever enough in the ways of TH to figure it out.
(Or (4) none of the above?)

Any thoughts or advice would be greatly appreciated!

thanks,
-Brent

[1] 
http://www.cs.chalmers.se/~rjmh/QuickCheck/quickcheckhttp://www.cs.chalmers.se/%7Erjmh/QuickCheck/quickcheck
[2] http://blog.codersbase.com/2006/09/01/simple-unit-testing-in-haskell/
[3] http://www.haskell.org/haskell
wiki/How_to_write_a_Haskell_program#Add_some_automated_testing:_QuickCheck
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reading/writing packed bytes from file

2007-06-20 Thread Duncan Coutts
On Wed, 2007-06-20 at 09:54 -0400, Jefferson Heard wrote:
 What about the Data.Binary module from the Hackage database?  I can call
 C, no problem, but I hate to do something that's already been done.

The current version of the binary package does everything you want
*except* for reading ieee float formats. So it's not suitable for you
yet sadly. It's pretty obvious that lots of people need this so it'll
probably get into the next version.

Duncan

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


RE: [Haskell-cafe] Haskell mode for emacs - some questions

2007-06-20 Thread Duncan Coutts
On Wed, 2007-06-20 at 21:29 +0200, peterv wrote:
 Yes this was also very very confusing for me because I had the same idea
 about that. I almost gave up on learning Haskell because of that (I wanted
 to practice stuff from the SOE book using the latest versions), until I
 suddenly found out that GHC *did* work.

Oh dear, if it's having that kind of effect I really had better fix it
then :-)

Duncan

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


Re: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-20 Thread Duncan Coutts
On Wed, 2007-06-20 at 16:53 -0700, Stefan O'Rear wrote:
 On Wed, Jun 20, 2007 at 04:49:55PM -0700, David Roundy wrote:
  To expand on that terse (but very true) statement, a list of Word8
  increases the space usage by a factor of probably around an order of
  magnitude (two pointers + 1 byte vs 1 byte), completely destroys your
 
 Three pointers.
 
 
 [ INFO PTR (like a tag but not quite) ]
 [ PTR to Word8 (these are hashconsed, thankfully) ]
 [ PTR to next value   ]

So that's 12 bytes on a 32bit box, or 24 or a 64bit one, to represent
one byte of data.

For comparison, ByteStrings have a bigger overhead but a lower linear
factor:

sizeof [Word8] of length n :
32bit: n * 12
64bit: n * 24

sizeof ByteString of length n :
32bit: 40 + n   (or 32 + n for shared bytestrings like substrings)
64bit: 80 + n   (or 64 + n for shared)

Incidentally a more space efficient representation that could preserve
the same operations speeds (like O(1) substring) would be:

data ByteString = BS ByteArray# Int Int

which would be 4 unshared words and 2 shared words rather than the
current 5 unshared and 4 shared that we get from using ForeignPtrs.

The smallest possible would be 2 words overhead by just using a
ByteArray#, but that sacrifices O(1) substring which is pretty important
for a functional style.

Duncan

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


Re: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-20 Thread Stefan O'Rear
On Thu, Jun 21, 2007 at 04:36:13AM +0100, Duncan Coutts wrote:
 The smallest possible would be 2 words overhead by just using a
 ByteArray#, but that sacrifices O(1) substring which is pretty important
 for a functional style.

Not necessarily the minimum!

data String
= S0
| S1 Word
| S2 Word
| S3 Word
| S4 Word
| S5 Word Word
| S6 Word Word
| S7 Word Word
| S8 Word Word
| S9 Word Word Word
| S10 Word Word Word
| S11 Word Word Word
| S12 Word Word Word
| S13 Word Word Word Word
| S14 Word Word Word Word
| S15 Word Word Word Word
| S16 Word Word Word Word
| S17 Word Word Word Word Word
| S18 Word Word Word Word Word
| S19 Word Word Word Word Word
| S20 Word Word Word Word Word
| SLong ByteArray#

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


Re: [Haskell-cafe] Using Template Haskell to automate QuickCheck testing?

2007-06-20 Thread Bulat Ziganshin
Hello Brent,

Thursday, June 21, 2007, 5:38:02 AM, you wrote:

 However, after reading all about TH it doesn't seem like there's a way
 to do this (reflecting on the current module to pull out the names of 
 certain top-level declarations).  

i don't know whether it's implemented, but standard workaround is to
put entire module body (or at least prop_*) in quotation brackets and explore
returned result, like this:

$(optimize [d| fib =  |])

just for case you don't know about this - i've written TH tutorial and doc:

http://www.haskell.org/bz/th3.htm
http://www.haskell.org/bz/thdoc.htm


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-20 Thread Bulat Ziganshin
Hello Anatoly,

Thursday, June 21, 2007, 3:11:13 AM, you wrote:

 implementation.  You should be able to stay within an order of
 magnitude from C with haskell without resorting to weird compiler
 tricks.

why you believe in it? are you ever implemented anything in Haskell
without tricks and it was only 10x slower than C equivalent?

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-20 Thread Bulat Ziganshin
Hello David,

Thursday, June 21, 2007, 3:49:55 AM, you wrote:

 A list of Word8 is -extremely- inefficient.

 To expand on that terse (but very true) statement, a list of Word8
 increases the space usage by a factor of probably around an order of
 magnitude (two pointers + 1 byte vs 1 byte), completely destroys your
 memory access pattern (which becomes random-access rather than sequential),
 and introduces additional nonlocal memory accesses.  One would hope that a
 hash function would be moderately close to being memory-limited, so we're
 talking about a multiple-order-of-magnitude slowdown.

if this list is produced lazily, then it will live in generation-2
area of GC which is 256kb large. lists are slow due to double laziness


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] haskell crypto is reaaaaaaaaaally slow

2007-06-20 Thread Bulat Ziganshin
Hello Duncan,

Thursday, June 21, 2007, 7:36:13 AM, you wrote:

 The smallest possible would be 2 words overhead by just using a
 ByteArray#,

i tried it once and found that ByteArray# size is returned rounded to 4 -
there is no way in GHC runtime to alloc, say, exactly 37 bytes. and
don't forget to add 2 unused bytes at average

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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