Re: [Haskell-cafe] What is the role of $!?

2007-11-17 Thread Jonathan Cast

On 17 Nov 2007, at 8:04 PM, PR Stanley wrote:


Hi
okay, so $! is a bit like $ i.e. the equivalent of putting  
parentheses around the righthand expression. I'm still not sure of  
the difference between $ and $!. Maybe it's because I don't  
understand the meaning of "strict application". While we're on the  
subject, what's meant by Haskell being a non-strict language?


In most languages, if you have some expression E, and when the  
computer attempts to evaluate E it goes in to an infinite loop, then  
when the computer attempts to evaluate the expression f(E), it also  
goes into an infinite loop, regardless of what f is.  That's the  
definition of a strict language.  In Haskell, this isn't the case ---  
we can write functions f such that the computation f(E)  terminates,  
even when E does not.  (:) is one such function, as are some  
functions built from it, such as (++); xn ++ ys terminates whenever  
xn does, even if ys is an infinite loop.  This is what makes it easy  
and convenient to build infinite loops in Haskell; in most strict  
languages, if you said


let fibs = 0 : 1 : zipWith (+) fibs (tail fibs)

the language would insist on evaluating fibs before it actually  
assigned anything to the memory cell for fibs, giving rise to an  
infinite loop.  (For this reason, most strict languages make such  
definitions compile-time errors).


Unfortunately, non-strictness turns out to be a pain in the ass to  
implement, since it means when the code generator sees an expression,  
it can't just generate code to evaluate it --- it has to hide the  
code somewhere else, and then substitute a pointer to that code for  
the value of the expression.  There are a number of clever  
optimizations you can use here (indeed, most of the history of  
Haskell compilation techniques is a list of clever techniques to get  
around the limitations of compiling non-strict languages), but most  
of them rely on the compiler knowing that, in this case, if a sub- 
expression is an infinite loop, the entire expression is an infinite  
loop.  This is actually pretty easy to figure out (most of the time),  
but sometimes the compiler needs a little help.


That's where $! (usually) comes in.  When the compiler sees (f $ x),  
it has to look at f to see whether, if x is an infinite loop, f $ x  
is one as well.  When the compiler sees (f $! x), it doesn't need to  
look at f --- if x is an infinite loop, (f $! x) always is one as  
well.  So, where in (f $ x) the compiler sometimes needs to put the  
code for x in a separate top-level block, to be called later when  
it's needed, in (f $! x) the compiler can always generate code for x  
inline, like a compiler for a normal language would.  Since most CPU  
architectures are optimized for normal languages that compile f(E) by  
generating code for E inline, this is frequently a big speed-up.


jcc

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


Re: [Haskell-cafe] What is the role of $!?

2007-11-17 Thread PR Stanley

Hi
okay, so $! is a bit like $ i.e. the equivalent of putting 
parentheses around the righthand expression. I'm still not sure of 
the difference between $ and $!. Maybe it's because I don't 
understand the meaning of "strict application". While we're on the 
subject, what's meant by Haskell being a non-strict language?

Cheers
Paul
At 01:50 15/11/2007, you wrote:

On 14 Nov 2007, at 4:32 PM, Shachaf Ben-Kiki wrote:


On Nov 14, 2007 4:27 PM, Justin Bailey <[EMAIL PROTECTED]> wrote:

It's:

  f $! x = x `seq` f x

That is, the argument to the right of $! is forced to evaluate, and
then that value is passed to the function on the left. The function
itself is not strictly evaluated (i.e., f x) I don't believe.


Unless you mean f -- which I still don't think would do much -- it
wouldn't make sense to evaluate (f x) strictly.


Right.  (f x) evaluates f and then applies it to x.  (f $! x)
evaluates x, evaluates f, and then applies f to x.

jcc

___
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] MD5?

2007-11-17 Thread Thomas DuBuisson
On Nov 17, 2007 11:40 AM, Andrew Coppin <[EMAIL PROTECTED]> wrote:
> As far as I know, mine is unique in that it's 100% Haskell and
> requires nothing aside from the libraries shipping with GHC in order to
> compile. (E.g., I downloaded somebody else's, and it just wouldn't
> compile. It was looking for modules that don't exist.)

Mines also a pure Haskell MD5 routine, though you do need Data.Binary
(which could be eliminated with minor effort).  Let me know if that
"sombody else's" MD5 routine that wouldn't compile was mine and what
the issue was - I'd be happy to fix it up a little if it would help.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Stream fusion for Hackage

2007-11-17 Thread Don Stewart
Just a quick announce: the stream fusion library for lists, 
that Duncan Coutts, Roman Leshchinskiy and I worked on earlier this year
is now available on Hackage as a standalone package:


http://hackage.haskell.org/cgi-bin/hackage-scripts/package/stream-fusion-0.1.1

As described in the recent paper:

"Stream Fusion: From Lists to Streams to Nothing at All"
Duncan Coutts, Roman Leshchinskiy and Don Stewart. ICFP 2007

This is a drop-in replacement for Data.List.

Haddocks here,

http://code.haskell.org/~dons/doc/stream-fusion/

(but note the interface is exactly the same as the Data.List library)

You might expect some small percent performance improvement for list
heavy programs, using ghc 6.8 and this list library with -O2 (use
-ddump-simpl-stats and look for:

STREAM stream/unstream fusion

messages, indicating your intermediate lists are getting removed.

To get an idea of what is happening, consider this list program:

foo :: Int -> Int
foo n = sum (replicate n 1)

Compiled with ghc-6.8.1 -O2 -ddump-simpl

Normally, as sum is a left fold, an intermediate lazy list is allocated
between the call to sum and replicate, as GHC currently does:

foo :: Int# -> Int#
foo n = Data.List.sum (case <=# n 0 of
False -> go n
True  -> [])
where
go :: Int# -> [Int]   -- intermediate list!
go n = case <=# n 1 of
False -> 1 : (go (n -# 1))
True  -> [1]

By using Data.List.Stream instead, you get a strict fused loop instead,
with no intermediate structure allocated:

loop_sum :: Int# -> Int# -> Int#
loop_sum k n  = case <=# n 0 of
False -> loop_sum (k +# 1) (n -# 1)
True  -> k

foo :: Int# -> Int#
foo n = loop_sum 0 n

This is a the halfway mark before porting other sequence types --
especially Data.ByteString -- over to the full stream fusion model (in
particular, strict bytestrings will benefit a lot, due to the O(n) cost
of intermediate bytestrings being removed).

The stream fusion types and combinators are also available in stripped
down form in the mlton sml compiler's extended prelude.

Enjoy.

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


Re: [Haskell-cafe] Re: [Haskell] AmeroHaskell

2007-11-17 Thread Derek Elkins
On Sat, 2007-11-17 at 17:38 -0800, Tim Chevalier wrote:
> On 11/17/07, Derek Elkins <[EMAIL PROTECTED]> wrote:
> > Don mentioned that.  However, something specifically Haskell and aimed
> > at a wider audience than just the Portland area is desirable.  It's also
> > a different tone than a user group.  Hopefully, there would be a reprise
> > next year in a different location.  That said, I imagine many of those
> > going to pdxfunc would be interested in AmeroHaskell and certainly it
> > could be set up as a pdxfunc meeting++.  At this point building momentum
> > for AmeroHaskell is what I'd like.
> >
> 
> Oh, ok, I think I probably just read your post too quickly. So you're
> going for something roughly equivalent to AngloHaskell?

Exactly.

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


Re: [Haskell-cafe] Re: [Haskell] AmeroHaskell

2007-11-17 Thread Tim Chevalier
On 11/17/07, Derek Elkins <[EMAIL PROTECTED]> wrote:
> Don mentioned that.  However, something specifically Haskell and aimed
> at a wider audience than just the Portland area is desirable.  It's also
> a different tone than a user group.  Hopefully, there would be a reprise
> next year in a different location.  That said, I imagine many of those
> going to pdxfunc would be interested in AmeroHaskell and certainly it
> could be set up as a pdxfunc meeting++.  At this point building momentum
> for AmeroHaskell is what I'd like.
>

Oh, ok, I think I probably just read your post too quickly. So you're
going for something roughly equivalent to AngloHaskell?

Cheers,
Tim

-- 
Tim Chevalier * catamorphism.org * Often in error, never in doubt
"...Losing your mind, like losing your car keys, is a real hassle." --
Andrew Solomon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] AmeroHaskell

2007-11-17 Thread Derek Elkins
On Sat, 2007-11-17 at 16:45 -0800, Tim Chevalier wrote:
> On 11/17/07, Derek Elkins <[EMAIL PROTECTED]> wrote:
> > However, to put things in motion for something concrete at all, we're
> > hoping to put together a meeting taking place in the Portland area as
> > that seems most convenient to the most people who had registered
> > interest in AmeroHaskell and an easy place to find a venue.  In that
> > vein, while no plans have been made, something aimed for the
> > January/February time-frame and probably hosted by Galois, if they are
> > willing, has been discussed.
> >
> 
> In Portland, we've already had the first pdxfunc meeting:
> http://groups.google.com/group/pdxfunc
> 
> While billed as a functional programming user group rather than a
> Haskell-specific group, we shouldn't duplicate effort.

Don mentioned that.  However, something specifically Haskell and aimed
at a wider audience than just the Portland area is desirable.  It's also
a different tone than a user group.  Hopefully, there would be a reprise
next year in a different location.  That said, I imagine many of those
going to pdxfunc would be interested in AmeroHaskell and certainly it
could be set up as a pdxfunc meeting++.  At this point building momentum
for AmeroHaskell is what I'd like.

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


[Haskell-cafe] Re: [Haskell] AmeroHaskell

2007-11-17 Thread Tim Chevalier
On 11/17/07, Derek Elkins <[EMAIL PROTECTED]> wrote:
> However, to put things in motion for something concrete at all, we're
> hoping to put together a meeting taking place in the Portland area as
> that seems most convenient to the most people who had registered
> interest in AmeroHaskell and an easy place to find a venue.  In that
> vein, while no plans have been made, something aimed for the
> January/February time-frame and probably hosted by Galois, if they are
> willing, has been discussed.
>

In Portland, we've already had the first pdxfunc meeting:
http://groups.google.com/group/pdxfunc

While billed as a functional programming user group rather than a
Haskell-specific group, we shouldn't duplicate effort.

Cheers,
Tim


-- 
Tim Chevalier * catamorphism.org * Often in error, never in doubt
"I don't know whether I believe in me, but I still believe in my
friends" -- Nerissa Nields
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Small optimisation question

2007-11-17 Thread Tim Chevalier
On 11/17/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:
> Suppose I write something like this:
>
>   foo :: [Int]
>   foo = concat (replicate 4 [4,7,2,9])
>
> The value of "foo" is completely determined at compile-time. So, will
> the compiler generate calls to concat and replicate, or will it just
> insert a large list constant here?
>

To add to what others have said, you might want to read the Simons'
paper "Secrets of the Glasgow Haskell Compiler Inliner":
http://research.microsoft.com/~simonpj/Papers/inlining/
It's pretty accessible, and talks about the various knobs that can be
twiddled in order to influence the black art of inlining.

Cheers,
Tim

-- 
Tim Chevalier * catamorphism.org * Often in error, never in doubt
"'There are no atheists in foxholes' isn't an argument against
atheism, it's an argument against foxholes." -- James Morrow
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Small optimisation question

2007-11-17 Thread David Menendez
On Nov 17, 2007 1:39 PM, Jake McArthur <[EMAIL PROTECTED]> wrote:
> On Nov 17, 2007, at 11:26 AM, Stefan O'Rear wrote:
>
> > The STG-machine was brilliant when it was designed, but times have
> > changed.  In particular, indirect jumps are no longer cheap.  Pointer
> > tagging has allowed STG to hobble into the 21st century, but really
> > the
> > air is ripe for a new abstract machine.
>
> Do you know of any candidates?

There's Boquist's GRIN. I believe JHC uses a variant of it.



-- 
Dave Menendez <[EMAIL PROTECTED]>

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


Re: [Haskell-cafe] Small optimisation question

2007-11-17 Thread Lennart Augustsson
There's no "the compiler". :)  There are many compilers.  I don't know of
any that evaluate those expressions at compile time, but it's certainly not
forbidden.  Nor would it be exceedingly hard to implement.
But it's not too bad to do it at run time either, because it will (most
likely) only be evaluated once at run time.

  -- Lennart

On Nov 17, 2007 4:01 PM, Andrew Coppin <[EMAIL PROTECTED]> wrote:

> Suppose I write something like this:
>
>  foo :: [Int]
>  foo = concat (replicate 4 [4,7,2,9])
>
> The value of "foo" is completely determined at compile-time. So, will
> the compiler generate calls to concat and replicate, or will it just
> insert a large list constant here?
>
> Obviously, once somebody has completely examined the contents of "foo",
> after that point it won't matter either way. I'm just curiose.
> Concatinating some strings is cheap; I sometimes write constructs like
> the above using much more expensive operations. (Expensive in time; the
> space taken up by the result isn't that great.)
>
> ___
> 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] Network.HTTP problem

2007-11-17 Thread Radosław Grzanka
Hi Graham,

2007/11/17, Graham Fawcett <[EMAIL PROTECTED]>:
> On Nov 17, 2007 4:52 PM, Radosław Grzanka <[EMAIL PROTECTED]> wrote:
> > > > Also:
> > > > $ ./get http://digg.com/rss/indexvideos_animation.xml
> >
> > However this one still seems to hang and eventually ends with :
> > get: recv: resource vanished (Connection reset by peer)
>
>
> It's not a Haskell problem. It looks like Digg expects a User-Agent
> request header. Modify get.hs like this:
>
> request uri = Request{ rqURI = uri,
>rqMethod = GET,
>rqHeaders = [Header HdrUserAgent 
> "haskell-get-example"],
>rqBody = "" }

Yes, that works. It's not only digg but other services as well..

Thank you for your help.
  Cheers,
   Radek.

-- 
Codeside: http://codeside.org/
Przedszkole Miejskie nr 86 w Lodzi: http://www.pm86.pl/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Network.HTTP problem

2007-11-17 Thread Graham Fawcett
On Nov 17, 2007 4:52 PM, Radosław Grzanka <[EMAIL PROTECTED]> wrote:
> > > Also:
> > > $ ./get http://digg.com/rss/indexvideos_animation.xml
>
> However this one still seems to hang and eventually ends with :
> get: recv: resource vanished (Connection reset by peer)


It's not a Haskell problem. It looks like Digg expects a User-Agent
request header. Modify get.hs like this:

request uri = Request{ rqURI = uri,
   rqMethod = GET,
   rqHeaders = [Header HdrUserAgent "haskell-get-example"],
   rqBody = "" }

and see what happens.

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


Re: [Haskell-cafe] Network.HTTP problem

2007-11-17 Thread Radosław Grzanka
Hi Bjorn,

I have tested the new version:

> > $ ./get http://www.podshow.com/feeds/gbtv.xml
> >
> > ... no-output ...

This case is indeed fixed. Thanks!

> >
> > Also:
> > $ ./get http://digg.com/rss/indexvideos_animation.xml

However this one still seems to hang and eventually ends with :
get: recv: resource vanished (Connection reset by peer)

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


Re: [Haskell-cafe] Network.HTTP problem

2007-11-17 Thread Radosław Grzanka
> This is now fixed and a new release with the fix is available from
> http://hackage.haskell.org/cgi-bin/hackage-scripts/package/HTTP-3001.0.1
>
> /Björn


Thank you very much! That was fast. I switched for the moment to curl
bindings but I will gladly turn back. :)

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


Re: [Haskell-cafe] Network.HTTP problem

2007-11-17 Thread Bjorn Bringert

On Nov 17, 2007, at 17:07 , Radosław Grzanka wrote:


Hello,
  I have a problem with Network.HTTP module
(http://www.haskell.org/http/) version 3001.0.0 . I have already
mailed Bjorn Bringert about it but I didn't get answer yet so maybe
someone here can help me. GHC v. 6.6.1 Ubuntu 7.10 x86_64 .

I have turned on debug flag.

Using get example (http://darcs.haskell.org/http/test/get.hs) I can
download pages like this:

$ ./get http://www.haskell.org/http/

http://www.w3.org/TR/xhtml1/DTD/xhtml1-strict.dtd";>
http://www.w3.org/1999/xhtml";>

Haskell HTTP package



 SNIP rest of the content SNIP 

Also the log contain content of this file.

However, some links misbehaves like:

$ ./get http://www.podshow.com/feeds/gbtv.xml

... no-output ...

however I see content of this xml in debug file and wget downloads
almost 250 kB of data.

Also:
$ ./get http://digg.com/rss/indexvideos_animation.xml

... hangs ...

and debug file has size 0, but wget downloads the file

I could suspect this is xml problem but:
$ ./get http://planet.haskell.org/rss20.xml


http://purl.org/dc/elements/1.1/";>


   Planet Haskell
   http://planet.haskell.org/
   en
   Planet Haskell -
http://planet.haskell.org/

 SNIP rest of the content SNIP 

so it works.
Do you have any idea what is going on here? What goes wrong? What
other (high level) modules could I use to download files through http?

Cheers,
 Radek.


Hi Radek,

thanks for the report.

This turned out to be a bug in how Network.HTTP handled Chunked  
Transfer Encoding. The web server sent the chunk size as  
"4000" (according to RFC 2616 this can be non-empty sequence of  
hex digits). However, Network.HTTP treated any chunk size starting  
with '0' as a chunk size of 0, which indicates the end of the chunked  
encoding.


This is now fixed and a new release with the fix is available from  
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/HTTP-3001.0.1


/Björn



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


Re: [Haskell-cafe] Re: Binary [was MD5]

2007-11-17 Thread Andrew Coppin

Aaron Denney wrote:

On 2007-11-17, Andrew Coppin <[EMAIL PROTECTED]> wrote:
  

  pack8into16 :: [Word8] -> Word16
  pack8into32 :: [Word8] -> Word32
  unpack16into8 :: Word16 -> [Word8]
  unpack32into8 :: Word32 -> [Word8]
  pack8into16s :: [Word8] -> [Word16]
  pack8into32s :: [Word8] -> [Word32]
  etc.

I had to write all these myself, by hand, and then check that I got 
everything the right way round and so forth. (And every now and then I 
find an edge case where these functions go wrong.)



Well, you know, some of these are really the wrong signatures:

pack8into16 :: (Word8, Word8) -> Word16
pack8into32 :: (Word8, Word8, Word8, Word8) -> Word32
unpack16into8 :: Word16 -> (Word8, Word8)
unpack32into8 :: Word32 -> (Word8, Word8, Word8, Word8)

curry the above to taste.
  


Yeah, but

 unpack16into8s = concatMap unpack16into8

;-)

Now if you just define some function splitN :: Int -> [x] -> [[x]] (I'm 
sure we've debated why this isn't defined already...), we can even write


 pack8into16s = map pack8into16 . splitN 16

And so we continue...

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


[Haskell-cafe] Re: MD5?

2007-11-17 Thread Aaron Denney
On 2007-11-17, Andrew Coppin <[EMAIL PROTECTED]> wrote:
>   pack8into16 :: [Word8] -> Word16
>   pack8into32 :: [Word8] -> Word32
>   unpack16into8 :: Word16 -> [Word8]
>   unpack32into8 :: Word32 -> [Word8]
>   pack8into16s :: [Word8] -> [Word16]
>   pack8into32s :: [Word8] -> [Word32]
>   etc.
>
> I had to write all these myself, by hand, and then check that I got 
> everything the right way round and so forth. (And every now and then I 
> find an edge case where these functions go wrong.)

Well, you know, some of these are really the wrong signatures:

pack8into16 :: (Word8, Word8) -> Word16
pack8into32 :: (Word8, Word8, Word8, Word8) -> Word32
unpack16into8 :: Word16 -> (Word8, Word8)
unpack32into8 :: Word32 -> (Word8, Word8, Word8, Word8)

curry the above to taste.

-- 
Aaron Denney
-><-

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


[Haskell-cafe] Re: Knot tying vs monads

2007-11-17 Thread apfelmus

John D. Ramsdell wrote:

Compared to that, I'm missing the specification part for your pretty

printer. How's it supposed to lay out?


The specification is in Paulson's book.  The pretty printer is used with
S-Expressions, and the block layout generates compact, indented output that
is good when there is much data to be displayed. ... The close
connection between the Haskell and Standard ML versions is part of the
reason I was able to quickly generate the code, and be confident in its
correctness.


Unfortunately, I don't have Paulson's book (or any other ML book :) at 
home. I'm too lazy to figure out the specification from the source code, 
can you provide a link or an explanation? I'm asking because I'd be 
astonished if one couldn't write an elegant Haskell version that's 
clearly correct and efficient at the same time. And such things are 
easiest to produce from scratch.



 a simple difference list ... will do.

Hmm.  Doesn't the output type (Int, String) -> (Int, String) show the
implementation is using the essence of a difference list?  Remember, the
resulting function prepends something the string it is given in the second
element of the pair, and returns that string.


Yes, of course. But the true virtue is to disentangle it from the rest, 
i.e. to use an abstract string type with fast concatenation.



  Int -> (Int, String -> String)   -- difference list


My first attempt at writing the printing function had a type similar to this
one.  I found myself composing difference lists of type ShowS.  The
performance was noticabily slow, specially as compared with the
implementation displayed in my message.  Perhaps the use of Data.DList would
repair this performance problem.

I don't mean to suggest that ShowS style difference lists cannot be used to
make the function easier to understand--all I'm saying is my attempt to do
so did not work out well.


Dlist a = [a] -> [a]  so this would be no different from ShowS.


Drop those strictness annotations from !String and ![Pretty], they won't

do any good. The !Int are only useful if they will be unboxed, but I
wouldn't bother right now.


I thought that the annotations ensure the first element of the list is
evaluated.  The Char and Pretty lists are generated with seqrev, so
everything gets evaluated before constructor is applied to data.

-- A reverse that evaluates the list elements.
seqrev :: [a] -> [a]
seqrev = foldl (\xs x -> x `seq` xs `seq` (x:xs)) []

The trouble is the constructors are not exported directly, but instead
through str, brk, and blo, functions which are not strict.  It's the best I
could do, as near as I can tell.


O_O, everything strict? But why would you ever want that?

Well if it's for "performance" reasons, I'd have to point out that the 
pretty printer has an algorithmic flaw: there are two calls to 
(breakdist es after), one from the  Brk  case and one from the  Blo 
case. The former one is safe since  breakdist  doesn't look further than 
to the next  Brk  in  es . But the latter one will lead to a quadratic 
run-time in the worst case, for example on the following input


  replicate n (Blk [Brk _] _ _)
  = [Blk [Brk _] _ _, Blk [Brk _] _ _, ..]  -- n elements

(Fill in any numbers you like for the placeholders _ ). That's a bit 
degenerate but you can spice it up with as many  Str  as you like, just 
don't add any additional  Brk .


Of course, a memoization scheme will fix this but I'd rather develop a 
new algorithm from scratch.



It seems rather hard to avoid lazyness in the current version of Haskell
when it's not wanted.  I hope one of the proposals for deep strictness makes
it into Haskell prime.  In my application, there is one datastructure, such
that if every value tracable from an instance of the datastructure is
evaluated, I am quite sure my program will be free from memory leaks due to
dragging.  I wish I could tell compilers to make it so.


As Derek said, strict data types are probably the easiest way to go 
here. Or you can use custom strict constructors, like


  str s = s `deepSeq` Str s

or something. But again, I don't know why you would want that at all.


Regards,
apfelmus

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


Re: [Haskell-cafe] Small optimisation question

2007-11-17 Thread jerzy . karczmarczuk
Stefan O'Rear writes: 


Jake McArthur wrote:

On Nov 17, 2007, at 11:26 AM, Stefan O'Rear wrote:



The STG-machine was brilliant when it was designed, but times have
changed.  ... really the
air is ripe for a new abstract machine.


Do you know of any candidates?

Hahaha - no.
(Do ask John Meacham though - he keeps *saying* he has a new AM...)
Stefan


I think that many people work on that, and the STG creators in particular.
SPJ regularly emits some papers on parallelisation. If I am not mistaken, 
the paper of both Simons and Tim Harris, about Haskell on a shared memory
multiprocessor, has more than two years. 


Some people speculate about making Haskell on the Clean G-machine, others
think about Java-like architectures... The world *IS* steadily progressing,
no need to hahaha-dynamite an open door saying that "the air is ripe...". 

Jerzy Karczmarczuk 



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


Re: [Haskell-cafe] MD5?

2007-11-17 Thread Don Stewart
bulat.ziganshin:
> Hello Andrew,
> 
> Saturday, November 17, 2007, 5:45:29 PM, you wrote:
> 
> > wasn't MD5 itself. It's all the datatype conversions. Nowhere in the
> > Haskell libraries can I find any of these functions:
> 
> > I had to write all these myself, by hand, and then check that I got
> 
> it's a good case for making useful library and put it to hackage ;)
> 
> you may wonder, but there is no paid army of haskellers which wrote
> all the libs you required. everything you've seen are written by
> enthusiasts just because they need it for their work
> 
> while working on my own program, i've made bindings to aes, twofish,
> sha512, pkcs5, fortune and lot of other C libs

Can you upload them to hackage Bulat? Under the Crypto category.
Even just the raw FFI decls will be useful.

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


Re: [Haskell-cafe] Re: Knot tying vs monads

2007-11-17 Thread Derek Elkins
On Sat, 2007-11-17 at 13:30 -0500, John D. Ramsdell wrote:
...

> It seems rather hard to avoid lazyness in the current version of
> Haskell when it's not wanted.  I hope one of the proposals for deep
> strictness makes it into Haskell prime.  In my application, there is
> one datastructure, such that if every value tracable from an instance
> of the datastructure is evaluated, I am quite sure my program will be
> free from memory leaks due to dragging.  I wish I could tell compilers
> to make it so. 

Use strict constructors.  Using strict data types is most probably the
appropriate way to deal with many cases where you would want a deep seq.
In particular, head strict lists would not be a bad addition.  There is
a library out there with several strict data types.

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


Re: [Haskell-cafe] Small optimisation question

2007-11-17 Thread Stefan O'Rear
On Sat, Nov 17, 2007 at 12:39:14PM -0600, Jake McArthur wrote:
> On Nov 17, 2007, at 11:26 AM, Stefan O'Rear wrote:
>
>> The STG-machine was brilliant when it was designed, but times have
>> changed.  In particular, indirect jumps are no longer cheap.  Pointer
>> tagging has allowed STG to hobble into the 21st century, but really the
>> air is ripe for a new abstract machine.
>
> Do you know of any candidates?

Hahaha - no.

(Do ask John Meacham though - he keeps *saying* he has a new AM...)

Stefan


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


Re: [Haskell-cafe] MD5?

2007-11-17 Thread Derek Elkins
On Sat, 2007-11-17 at 16:40 +, Andrew Coppin wrote:
> Thomas DuBuisson wrote:
> >> BTW, while I'm here... I sat down and wrote my own MD5 implementation.
> >> 
> >
> > How is the performance on this new MD5 routine?
> 
> Ask me *after* I modify it to give the correct answers. ;-)
> 
> Interesting question: How do you determine when an implementation of 
> something as complex as MD5 is actually "correct"? I might get it so it 
> passes all the tests I've tried, but there's some obscure edge case that 
> makes it fail. How would you know that? Hmm, in fact... how do I know 
> the implementation(s) in checking my program *against* are correct?

It's a small enough program that it should not be that hard to prove
that it does the same thing as the reference implementation (although,
that one may be broken...)

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


Re: [Haskell-cafe] Small optimisation question

2007-11-17 Thread Jake McArthur

On Nov 17, 2007, at 11:26 AM, Stefan O'Rear wrote:


The STG-machine was brilliant when it was designed, but times have
changed.  In particular, indirect jumps are no longer cheap.  Pointer
tagging has allowed STG to hobble into the 21st century, but really  
the

air is ripe for a new abstract machine.


Do you know of any candidates?

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


Re: [Haskell-cafe] Re: Knot tying vs monads

2007-11-17 Thread John D. Ramsdell
Thank you for your interesting reply.  I found it enlightening.

Compared to that, I'm missing the specification part for your pretty
> printer. How's it supposed to lay out?


The specification is in Paulson's book.  The pretty printer is used with
S-Expressions, and the block layout generates compact, indented output that
is good when there is much data to be displayed.  I played around with the
Hughes pretty printer, but it wasn't obvious how to get the output I knew I
could from the Paulson pretty printer.  I confess I did not spend much time
tinkering with the Hughes pretty printer.

I failed to mention in my original note that the code was written so that
the Haskell version lines up with the Standard ML version.  The close
connection between the Haskell and Standard ML versions is part of the
reason I was able to quickly generate the code, and be confident in its
correctness.  It also explains why I did not use the sum function in the
Prelude, or your map trick when writing the blo function.

> What style do to you prefer, a knot-tying or a monad-based style?  I
> have enclosed the pretty printer.  The printing function is the
> subject of the controversy.

... a simple difference list ... will do.


Hmm.  Doesn't the output type (Int, String) -> (Int, String) show the
implementation is using the essence of a difference list?  Remember, the
resulting function prepends something the string it is given in the second
element of the pair, and returns that string.

Introducing a difference list means to replace the output type
>
>   (Int, String) -> (Int, String)
>
> of  printing  by
>
>   Int -> (Int, String -> String)   -- difference list
>

My first attempt at writing the printing function had a type similar to this
one.  I found myself composing difference lists of type ShowS.  The
performance was noticabily slow, specially as compared with the
implementation displayed in my message.  Perhaps the use of Data.DList would
repair this performance problem.

I don't mean to suggest that ShowS style difference lists cannot be used to
make the function easier to understand--all I'm saying is my attempt to do
so did not work out well.

>> module Pretty(Pretty, pr, blo, str, brk) where
>
>> data Pretty
>> = Str !String
>> | Brk !Int  -- Int is the number of breakable spaces
>> | Blo ![Pretty] !Int !Int -- First int is the indent, second int
>> --  is the number of chars and spaces for strings and breaks in block

Drop those strictness annotations from !String and ![Pretty], they won't
> do any good. The !Int are only useful if they will be unboxed, but I
> wouldn't bother right now.


I thought that the annotations ensure the first element of the list is
evaluated.  The Char and Pretty lists are generated with seqrev, so
everything gets evaluated before constructor is applied to data.

-- A reverse that evaluates the list elements.
seqrev :: [a] -> [a]
seqrev = foldl (\xs x -> x `seq` xs `seq` (x:xs)) []

The trouble is the constructors are not exported directly, but instead
through str, brk, and blo, functions which are not strict.  It's the best I
could do, as near as I can tell.

It seems rather hard to avoid lazyness in the current version of Haskell
when it's not wanted.  I hope one of the proposals for deep strictness makes
it into Haskell prime.  In my application, there is one datastructure, such
that if every value tracable from an instance of the datastructure is
evaluated, I am quite sure my program will be free from memory leaks due to
dragging.  I wish I could tell compilers to make it so.

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


Re: [Haskell-cafe] My MD5

2007-11-17 Thread Andrew Coppin

Thomas DuBuisson wrote:

BTW, while I'm here... I sat down and wrote my own MD5 implementation.



Huzzah! It works! :-D

I had a silly bug where somewhere deep in the heart of the huge complex 
message padding algorithm, I forgot to add on the cumulative total to 
the message size count. This results in the number of bits in the 
*final* block being used, rather than the number of bits in the entire 
message. Oops!



How is the performance on this new MD5 routine?


Not good. (Surprised?)

I told it to hash a 1 MB file, and there was a noticable split-second 
pause. I told it to hash a 400 MB file, and... well, after about 1 
minute wall time and 200 MB RAM I killed the process. RAM usage seems to 
grow linearly with time, which is Not Good(tm). To me, this suggests 
that something somewhere isn't as lazy as it should be. Hmm. Well 
whatever, next stop is the GHC profiler to see where my resources are 
going. Given the above bug, it's probably something easily fixable...


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


Re: [Haskell-cafe] Small optimisation question

2007-11-17 Thread Andrew Coppin

Stefan O'Rear wrote:

On Sat, Nov 17, 2007 at 04:31:33PM +, Andrew Coppin wrote:
  
Well, presumably the guys who designed STG did it this way for a really 
good reason, and they know far more than me, so... ;-)



The STG-machine was brilliant when it was designed, but times have
changed.  In particular, indirect jumps are no longer cheap.  Pointer
tagging has allowed STG to hobble into the 21st century, but really the
air is ripe for a new abstract machine.
  


You volunteering? 0;-)

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


Re: [Haskell-cafe] Small optimisation question

2007-11-17 Thread Stefan O'Rear
On Sat, Nov 17, 2007 at 04:31:33PM +, Andrew Coppin wrote:
>> Both.  A curious feature of the STG machine is that constructor thunks
>> and evaluated data are represented identically in memory.
>
> Ooo... As per the Lambdacats "Boxed cat has a uniform representation"?
>
> Well, presumably the guys who designed STG did it this way for a really 
> good reason, and they know far more than me, so... ;-)

The STG-machine was brilliant when it was designed, but times have
changed.  In particular, indirect jumps are no longer cheap.  Pointer
tagging has allowed STG to hobble into the 21st century, but really the
air is ripe for a new abstract machine.

Stefan


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


Re: [Haskell-cafe] MD5?

2007-11-17 Thread Andrew Coppin

Thomas DuBuisson wrote:

BTW, while I'm here... I sat down and wrote my own MD5 implementation.



How is the performance on this new MD5 routine?


Ask me *after* I modify it to give the correct answers. ;-)

Interesting question: How do you determine when an implementation of 
something as complex as MD5 is actually "correct"? I might get it so it 
passes all the tests I've tried, but there's some obscure edge case that 
makes it fail. How would you know that? Hmm, in fact... how do I know 
the implementation(s) in checking my program *against* are correct?


Oh noes! I'm becoming a paranoid cryptographer! LOL.


It looks like we have
gone from just one Haskell MD5 implementation (that I know of) to
three in a short period of time.  This isn't counting the C bindings,
of coarse.

Also, I changed the license of my implementation to BSD3 a bit ago, so
you can use that pretty much as you please.
  


Yeah, there seem to be a few different MD5 implementations floating 
around. As far as I know, mine is unique in that it's 100% Haskell and 
requires nothing aside from the libraries shipping with GHC in order to 
compile. (E.g., I downloaded somebody else's, and it just wouldn't 
compile. It was looking for modules that don't exist.)


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


Re: [Haskell-cafe] Small optimisation question

2007-11-17 Thread Andrew Coppin

Stefan O'Rear wrote:

On Sat, Nov 17, 2007 at 04:10:58PM +, Andrew Coppin wrote:
  


OK. I presume this is due to the fact that the result of executing an 
expression at compile-time could be arbitrarily large?



Yes, and it's not even guaranteed to terminate.
  


That would be "arbitrarily large", yes. ;-)


Are there any buttons that can be twiddled to control this behaviour?



Not that I'm aware of, though you can hack something with RULEs
probably.
  


I was just wondering whether there was some way to say "please unravel 
this expression until the result is X units big" or something. Oh well.


(I'm sure Template Haskell could do it if you wanted it that badly... or 
just write a small Haskell program that writes a Haskell program. Eeps!)


For that matter, when I say "[4,7,2,9]", what does that compile into? Some 
data structures in memory? Or code to actually build said structures?



Both.  A curious feature of the STG machine is that constructor thunks
and evaluated data are represented identically in memory.
  


Ooo... As per the Lambdacats "Boxed cat has a uniform representation"?

Well, presumably the guys who designed STG did it this way for a really 
good reason, and they know far more than me, so... ;-)


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


Re: [Haskell-cafe] MD5?

2007-11-17 Thread Thomas DuBuisson
> BTW, while I'm here... I sat down and wrote my own MD5 implementation.

How is the performance on this new MD5 routine?  It looks like we have
gone from just one Haskell MD5 implementation (that I know of) to
three in a short period of time.  This isn't counting the C bindings,
of coarse.

Also, I changed the license of my implementation to BSD3 a bit ago, so
you can use that pretty much as you please.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] MD5?

2007-11-17 Thread Bulat Ziganshin
Hello Andrew,

Saturday, November 17, 2007, 7:13:23 PM, you wrote:

> Out of curiosity, what's hackage, and how do you put stuff on it?

google for "haskell hackage". i never uploaded anything to it, but
site should contain instructions

>> while working on my own program, i've made bindings to aes, twofish,
>> sha512, pkcs5, fortune and lot of other C libs

> I don't know C, so I can't really write bindings. (I also don't have a C
> compiler for that matter... Presumably I'd have to move to Linux for that.)

i don't think that C knowledge is really reqd, but you should
understand cpu memory model. there is also "ffi packaging tool" which
should generate bindings automatically. C and C++ compilers are
shipped as part of GHC/win32 distribution


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Small optimisation question

2007-11-17 Thread Stefan O'Rear
On Sat, Nov 17, 2007 at 04:10:58PM +, Andrew Coppin wrote:
> Stefan O'Rear wrote:
>> On Sat, Nov 17, 2007 at 04:01:34PM +, Andrew Coppin wrote:
>>   
>>> Suppose I write something like this:
>>>
>>>  foo :: [Int]
>>>  foo = concat (replicate 4 [4,7,2,9])
>>>
>>> The value of "foo" is completely determined at compile-time. So, will the 
>>> compiler generate calls to concat and replicate, or will it just insert a 
>>> large list constant here?
>>> 
>> The compiler will generate calls to concat and replicate.
>>   
>
> OK. I presume this is due to the fact that the result of executing an 
> expression at compile-time could be arbitrarily large?

Yes, and it's not even guaranteed to terminate.

> Are there any buttons that can be twiddled to control this behaviour?

Not that I'm aware of, though you can hack something with RULEs
probably.

> For that matter, when I say "[4,7,2,9]", what does that compile into? Some 
> data structures in memory? Or code to actually build said structures?

Both.  A curious feature of the STG machine is that constructor thunks
and evaluated data are represented identically in memory.

Stefan


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


Re: [Haskell-cafe] MD5?

2007-11-17 Thread Andrew Coppin

Bulat Ziganshin wrote:

Hello Andrew,

Saturday, November 17, 2007, 5:45:29 PM, you wrote:

  

wasn't MD5 itself. It's all the datatype conversions. Nowhere in the
Haskell libraries can I find any of these functions:



  

I had to write all these myself, by hand, and then check that I got



it's a good case for making useful library and put it to hackage ;)

you may wonder, but there is no paid army of haskellers which wrote
all the libs you required. everything you've seen are written by
enthusiasts just because they need it for their work
  


Just looked like something that would be frequently required, but anyway...

Out of curiosity, what's hackage, and how do you put stuff on it?


while working on my own program, i've made bindings to aes, twofish,
sha512, pkcs5, fortune and lot of other C libs
  


I don't know C, so I can't really write bindings. (I also don't have a C 
compiler for that matter... Presumably I'd have to move to Linux for that.)


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


Re: [Haskell-cafe] Small optimisation question

2007-11-17 Thread Andrew Coppin

Stefan O'Rear wrote:

On Sat, Nov 17, 2007 at 04:01:34PM +, Andrew Coppin wrote:
  

Suppose I write something like this:

 foo :: [Int]
 foo = concat (replicate 4 [4,7,2,9])

The value of "foo" is completely determined at compile-time. So, will the 
compiler generate calls to concat and replicate, or will it just insert a 
large list constant here?


The compiler will generate calls to concat and replicate.
  


OK. I presume this is due to the fact that the result of executing an 
expression at compile-time could be arbitrarily large?


Are there any buttons that can be twiddled to control this behaviour?


For that matter, when I say "[4,7,2,9]", what does that compile into? 
Some data structures in memory? Or code to actually build said structures?


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


[Haskell-cafe] Network.HTTP problem

2007-11-17 Thread Radosław Grzanka
Hello,
  I have a problem with Network.HTTP module
(http://www.haskell.org/http/) version 3001.0.0 . I have already
mailed Bjorn Bringert about it but I didn't get answer yet so maybe
someone here can help me. GHC v. 6.6.1 Ubuntu 7.10 x86_64 .

I have turned on debug flag.

Using get example (http://darcs.haskell.org/http/test/get.hs) I can
download pages like this:

$ ./get http://www.haskell.org/http/

http://www.w3.org/TR/xhtml1/DTD/xhtml1-strict.dtd";>
http://www.w3.org/1999/xhtml";>

Haskell HTTP package



 SNIP rest of the content SNIP 

Also the log contain content of this file.

However, some links misbehaves like:

$ ./get http://www.podshow.com/feeds/gbtv.xml

... no-output ...

however I see content of this xml in debug file and wget downloads
almost 250 kB of data.

Also:
$ ./get http://digg.com/rss/indexvideos_animation.xml

... hangs ...

and debug file has size 0, but wget downloads the file

I could suspect this is xml problem but:
$ ./get http://planet.haskell.org/rss20.xml


http://purl.org/dc/elements/1.1/";>


   Planet Haskell
   http://planet.haskell.org/
   en
   Planet Haskell -
http://planet.haskell.org/

 SNIP rest of the content SNIP 

so it works.
Do you have any idea what is going on here? What goes wrong? What
other (high level) modules could I use to download files through http?

Cheers,
 Radek.

-- 
Codeside: http://codeside.org/
Przedszkole Miejskie nr 86 w Lodzi: http://www.pm86.pl/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Small optimisation question

2007-11-17 Thread Stefan O'Rear
On Sat, Nov 17, 2007 at 04:01:34PM +, Andrew Coppin wrote:
> Suppose I write something like this:
>
>  foo :: [Int]
>  foo = concat (replicate 4 [4,7,2,9])
>
> The value of "foo" is completely determined at compile-time. So, will the 
> compiler generate calls to concat and replicate, or will it just insert a 
> large list constant here?
>
> Obviously, once somebody has completely examined the contents of "foo", 
> after that point it won't matter either way. I'm just curiose. 
> Concatinating some strings is cheap; I sometimes write constructs like the 
> above using much more expensive operations. (Expensive in time; the space 
> taken up by the result isn't that great.)

The compiler will generate calls to concat and replicate.

Stefan, who is pretty sure he has a proposal for generalized folding
pragmas

Stefan


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


[Haskell-cafe] Small optimisation question

2007-11-17 Thread Andrew Coppin

Suppose I write something like this:

 foo :: [Int]
 foo = concat (replicate 4 [4,7,2,9])

The value of "foo" is completely determined at compile-time. So, will 
the compiler generate calls to concat and replicate, or will it just 
insert a large list constant here?


Obviously, once somebody has completely examined the contents of "foo", 
after that point it won't matter either way. I'm just curiose. 
Concatinating some strings is cheap; I sometimes write constructs like 
the above using much more expensive operations. (Expensive in time; the 
space taken up by the result isn't that great.)


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


Re[2]: [Haskell-cafe] MD5?

2007-11-17 Thread Bulat Ziganshin
Hello Andrew,

Saturday, November 17, 2007, 5:45:29 PM, you wrote:

> wasn't MD5 itself. It's all the datatype conversions. Nowhere in the
> Haskell libraries can I find any of these functions:

> I had to write all these myself, by hand, and then check that I got

it's a good case for making useful library and put it to hackage ;)

you may wonder, but there is no paid army of haskellers which wrote
all the libs you required. everything you've seen are written by
enthusiasts just because they need it for their work

while working on my own program, i've made bindings to aes, twofish,
sha512, pkcs5, fortune and lot of other C libs

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] MD5?

2007-11-17 Thread Andrew Coppin

Neil Mitchell wrote:

Hi

  

The MD5SUM.EXE file I have chokes if you ask it to hash a file in
another directory. It will hash from stdin, or from a file in the
current directory, but point-blank refuses to hash anything else.



Try http://www.cs.york.ac.uk/fp/yhc/dependencies/UnxUtils.zip - that
has an MD5SUM program in it that seems to work fine on things in
different directories. It also has many other great utilities in it.
  


Negative. It gives strange output if the pathname contains any 
backslashes. (Each backslash appears twice, and an additional backslash 
appears just before the hash value. Very odd...)


I spent a while playing with Google, and found many, many 
implementations of MD5. Every single one of them did *something* strange 
under certain conditions. Most frustrating! Well anyway, I eventually 
settled on a program MD5DEEP.EXE, which seems to work just about well 
enough to be useful.



I'm trying to imagine what mistake the authors of your version of
MD5SUM must have made to screw up files in different directories, but
it eludes me...
  


It seems typically Unix tools are compiled for Windows with the aid of a 
Unix emulator. These often do all sorts of strange path munging to make 
Windows look like Unix. That's probably the source of the problem...




BTW, while I'm here... I sat down and wrote my own MD5 implementation. 
It's now 95% working. (The padding algorithm goes wrong for certain 
message lengths.) I doubt it'll ever be fast, but I wanted to see how 
hard it would be to implement. The hard part, ridiculously enough, 
wasn't MD5 itself. It's all the datatype conversions. Nowhere in the 
Haskell libraries can I find any of these functions:


 pack8into16 :: [Word8] -> Word16
 pack8into32 :: [Word8] -> Word32
 unpack16into8 :: Word16 -> [Word8]
 unpack32into8 :: Word32 -> [Word8]
 pack8into16s :: [Word8] -> [Word16]
 pack8into32s :: [Word8] -> [Word32]
 etc.

I had to write all these myself, by hand, and then check that I got 
everything the right way round and so forth. (And every now and then I 
find an edge case where these functions go wrong.) Of course, on top of 
that, MD5 uses something really stupid called "little endian integers". 
In other words, to interpret the data, you have to read it partially 
backwards, partially forwards. Really awkward to get right!


But, after a few hours last night and a few more this morning, I was 
able to get the main program to work properly. If I can just straighten 
out the message padding code, I'll be all set... Then I can see about 
measuring just how slow it is. :-}


Most amusing moment: Trying to run the GHC debugger, and then realising 
that you have to actually install the new version of GHC first...


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