[Haskell-cafe] Re: (a - [b]) vs. [a - b]

2007-02-03 Thread apfelmus
Chad Scherrer wrote:
 Unfortunately, I was trying to give a simplification of the real
 problem, where the monad is STM instead of []. Based on apfelmus's
 observation of why they can't be isomorphic, I'm guessing I'm out of
 luck.
 
 http://www.haskell.org/pipermail/haskell-cafe/2006-December/020041.html
 
 So in reality, I'm trying to construct something like
 f :: (a - STM b) - STM (a - b)

Indeed, such an f most likely does not exist. What is the task you tried
to solve with the help of f? I guess that either there is a way without
or it just cannot be solved for mathematical reasons.

Regards,
apfelmus

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


Re: [Haskell-cafe] Suggestions for a hReadUntilStr implementation

2007-02-03 Thread Martin DeMello

On 2/3/07, Matt Revelle [EMAIL PROTECTED] wrote:


hReadUntilStr :: (Num a) = Handle - String - a - IO (String, Bool)

Is this the wrong way to think about the problem?  If so, how should
it be handled?  If not, any ideas on the implementation?


Sounds like this would grow into a full-fledged expect-type program,
in which case http://www.informatik.uni-bremen.de/uniform/wb/ is
probably worth a look.

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


Re: [Haskell-cafe] Alternate instance Show (Maybe a)?

2007-02-03 Thread Bjorn Bringert

On Feb 2, 2007, at 21:10 , Sergey Zaharchenko wrote:


Hello list,

Suppose I want show Nothing to return , and show (Just foo) return
show foo. I don't seem to be able to. Looks like I either have to use
some other function name, like `mShow', or have to import Prelude  
hiding
Maybe, reimplement Maybe, write all the other useful instances  
(Functor,
Monad) for it, etc. Not particularly hard, but looks ugly. Isn't  
there a
better solution? I recall some discussion about this, but can't  
find it

in the archives...


With GHC you can at least avoid rewriting all the instances: make a  
newtype, use newtype deriving to get all the instances except Show,  
and write your own Show instance.


 {-# OPTIONS_GHC -fglasgow-exts #-}

 newtype MyMaybe a = MyMaybe (Maybe a)
  deriving (Eq,Ord,Monad,Functor)

 instance Show a = Show (MyMaybe a) where
   showsPrec _ (MyMaybe Nothing)  = id
   showsPrec n (MyMaybe (Just x)) = showsPrec n x

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


Re: [Haskell-cafe] Re: (a - [b]) vs. [a - b]

2007-02-03 Thread Tomasz Zielonka
On Sat, Feb 03, 2007 at 10:13:17AM +0100, [EMAIL PROTECTED] wrote:
 Chad Scherrer wrote:
  So in reality, I'm trying to construct something like
  f :: (a - STM b) - STM (a - b)
 
 Indeed, such an f most likely does not exist.

Yes, consider:
f readTVar :: STM (TVar c - c)
That would be pretty dangerous.

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


Re: [Haskell-cafe] How did you stumble on Haskell?

2007-02-03 Thread Lennart Augustsson

On Jan 29, 2007, at 03:01 , Alexy Khrabrov wrote:


How do people stumble on Haskell?


Well, I didn't really stumble on it.  I was at the 1987 meeting
when we decided to define Haskell.

But I stumbled on functional programming in the first place.
I had to learn it because it was part of a course in denotational
semantics.  The language was SASL.  And then I read David Turners
paper on combinators, and I was hooked.

-- Lennart

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


Re: [Haskell-cafe] How did you stumble on Haskell?

2007-02-03 Thread Joel Reymont

I'll go for the shortest story...

I stumbled upon Simon's Composing Financial Contracts paper, Simon  
was gracious enough to spend a fair bit of time on the phone with me.


The rest is history :-).

Joel

--
http://wagerlabs.com/





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


[Haskell-cafe] Re: How did you stumble on Haskell?

2007-02-03 Thread Jón Fairbairn
Lennart Augustsson [EMAIL PROTECTED] writes:

 On Jan 29, 2007, at 03:01 , Alexy Khrabrov wrote:
 
  How do people stumble on Haskell?
 
 Well, I didn't really stumble on it.  I was at the 1987 meeting
 when we decided to define Haskell.
 
 But I stumbled on functional programming in the first place.
 I had to learn it because it was part of a course in denotational
 semantics. 

OK, if we old lags are going to give our excuses... I was a
member of an undergraduate society in Cambridge called the
Processor Group.  I went along to a talk that Arthur Norman
gave to them (must have been 1980±1?) in which he described
(S, K, I) combinators and his plans for the SKI Machine
(SKIM). The fact that S and K on their own gave a complete
computational basis was the most exciting piece of computer
science I'd encountered at that point and I just had to
follow it up. So some years later I ended up at that same
1987 meeting.

-- 
Jón Fairbairn [EMAIL PROTECTED]


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


Re: [Haskell-cafe] How did you stumble on Haskell?

2007-02-03 Thread Paul Johnson
 In about 93 or 94 a colleague had talked to me about this wierd 
language called Haskell. At the time I hadn't listened because I was 
sure that Eiffel was the future. Besides, he had showed me a GUI demo: a 
calculator that took about half a second to register a button click. So 
I concluded that it wasn't practical.


Fast forward to about 2001. I was in a job where I almost never got to 
do any programming. It had become painfully obvious that Eiffel wasn't 
going anywhere. I could always learn Java, but after Eiffel downgrading 
to Java felt like a sell-out: I wasn't going to do it. But I did want to 
learn a new language, and I'd read Eric Raymond's piece about being a 
hacker, where he said to learn Lisp for the side effects. I sort-of knew 
Lisp anyway, having done some Emacs Lisp hacking. But I felt I didn't 
really get it about FP. There seemed to be a lot of buzz about Haskell, 
so I took the plunge and started learning.


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


[Haskell-cafe] Re: How did you stumble on Haskell?

2007-02-03 Thread Jón Fairbairn
Paul Johnson [EMAIL PROTECTED] writes:

 I'd read Eric Raymond's piece about being a hacker, where
 he said to learn Lisp for the side effects.

Much better to learn Haskell for the side effects! ;-)

-- 
Jón Fairbairn [EMAIL PROTECTED]

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


Re: [Haskell-cafe] How did you stumble on Haskell?

2007-02-03 Thread Colin Paul Adams
 Paul == Paul Johnson [EMAIL PROTECTED] writes:

Paul because I was sure that Eiffel was the future.

You were right!

Paul It had become painfully
Paul obvious that Eiffel wasn't going anywhere.

Hm. Why do I make a living at it then? And why is there now an ECMA
standard for it?

Paul learn Java, but after Eiffel downgrading to Java felt like a
Paul sell-out:

That's true.

Anyway, my story about how I stumbled across Haskell:

I was visiting Glasgow for the Scottish Go championships, and was
talking to John O'Donnell in the bar about what functional programming
was all about. I mentioned that I knew Scheme, and he said he much
preferred Haskell. So I tried to get him to describe the language to
me, but he seemed more interested in playing Go.

So I just had to learn it when i got home again, to find out about it.
-- 
Colin Adams
Preston Lancashire
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Proposal for allowing more use of layout to avoid parentheses and commas

2007-02-03 Thread Brian Hulley

Hi,
Following a recent thread on the Haskell' mailing list about the nusiance of 
having to deal with commas in tuples (when cutting and pasting things to 
re-order the elements there's always a pesky comma left over in the wrong 
place), I've written up a proposal for a very simple syntax tweak that would 
allow you to use the layout rule for function arguments, tuple/list/record 
contents etc for some future version of Haskell at 
http://www.haskell.org/haskellwiki/Accessible_layout_proposal


This post is not intended to spark a lot of discussion just to point out the 
existence of the page for anyone interested. I've also added a link to all 
the new proposals from http://www.haskell.org/haskellwiki/Future .


(If I don't reply to any follow up posts to this thread it's not because I'm 
ignoring them. It will just be because I have to try to get down to actually 
writing more of my program in the next few weeks, and I find thinking up 
ideas and reading posts, books, cooking, shopping, watching dvds etc, is 
infinitely more diverting than the painstakingly hard work of actual coding 
(though of course it's great in the rare occasions when things fall into 
place) ... ;-))


Brian.
--
http://www.metamilk.com 


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


Re: [Haskell-cafe] Alternate instance Show (Maybe a)?

2007-02-03 Thread Yitzchak Gale

Hi Sergey,

You wrote:

Suppose I want show Nothing to return , and show (Just foo) return
show foo. I don't seem to be able to. Looks like I either have to use
some other function name, like `mShow'


That is correct.

Show instances are supposed to follow the convention that
show x is a Haskell expression that recreates x. In other words,
Show is mainly used for debugging, for simple serialization, and
for interactive use in a Haskell shell like ghci or hugs.

If you need to create strings from a datatype for some other
reason, use a different function name. If you need to do it
for several datatypes, create your own class.

Of course, Show does turn out to be more generally
useful for numeric types.

Hope this helps.

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


[Haskell-cafe] Space Leak Help

2007-02-03 Thread Dominic Steinitz
I have re-written SHA1 so that is more idiomatically haskell and it is easy to 
see how it implements the specification. The only problem is I now have a 
space leak. I can see where the leak is but I'm less sure what to do about 
getting rid of it.

Here's the offending function:

pad :: [Word8] - [Word8]
pad xs =
   xs ++ [0x80] ++ ps ++ lb
   where
  l = length xs
  pl = (64-(l+9)) `mod` 64
  ps = replicate pl 0x00
  lb = i2osp 8 (8*l)

I've thought about zipping the xs with [1..] which will give me a length as I 
go. Is this the right way to go are there better techniques for dealing with 
this?

I've attached the full source below.

Dominic.

module Main(main) where

import Data.Char
import Data.Bits
import Data.List
import Data.Word
import System
import Codec.Utils

type Rotation = Int

rotL :: Rotation - Word32 - Word32
rotL s a = shiftL a s .|. shiftL a (s-32)

instance Num [Word32] where
   a + b = zipWith (+) a b

f n x y z 
   | (0 = n)   (n = 19) = (x .. y) .|. ((complement x) .. z)
   | (20 = n)  (n = 39) = x `xor` y `xor` z
   | (40 = n)  (n = 59) = (x .. y) .|. (x .. z) .|. (y .. z)
   | (60 = n)  (n = 79) = x `xor` y `xor` z
   | otherwise = error invalid index for f

k n
   | (0 = n)   (n = 19) = 0x5a827999
   | (20 = n)  (n = 39) = 0x6ed9eba1
   | (40 = n)  (n = 59) = 0x8f1bbcdc
   | (60 = n)  (n = 79) = 0xca62c1d6
   | otherwise = error invalid index for k

-- Word120 - Word512 - Word120 
oneBlock ss xs = (as!!80):(bs!!80):(cs!!80):(ds!!80):(es!!80):[]
   where
  ws = xs ++ map (rotL 1) (zipWith4 xxxor wm3s wm8s wm14s wm16s)
 where 
xxxor a b c d = a `xor` b `xor` c `xor` d
wm3s  = drop (16-3)  ws
wm8s  = drop (16-8)  ws
wm14s = drop (16-14) ws
wm16s = drop (16-16) ws
  as = (ss!!0):ts
  bs = (ss!!1):as
  cs = (ss!!2):(map (rotL 30) bs)
  ds = (ss!!3):cs 
  es = (ss!!4):ds
  ts = (map (rotL 5) as) + (zipWith4 f [0..] bs cs ds) + es + (map k 
[0..]) + ws

ss :: [Word32]
ss = [0x67452301, 0xefcdab89, 0x98badcfe, 0x10325476, 0xc3d2e1f0]

pad :: [Word8] - [Word8]
pad xs =
   xs ++ [0x80] ++ ps ++ lb
   where
  l = length xs
  pl = (64-(l+9)) `mod` 64
  ps = replicate pl 0x00
  lb = i2osp 8 (8*l)

blockWord8sIn512 :: [Word8] - [[Word8]]
blockWord8sIn512 =
   unfoldr g
   where
  g [] = Nothing
  g xs = Just (splitAt 64 xs)

getWord32s :: [Word8] - [Word32]
getWord32s s = 
   map f [0..15]
   where 
  f i = foldl (+) 0 $ map (\n - toEnum (fromEnum (s!!(i*4+n))) `shiftL` 
(fromIntegral (8 * (3-n [0..3]

blockWord32sIn512 :: [Word8] - [[Word32]]
blockWord32sIn512 = (map getWord32s) . blockWord8sIn512 . pad

-- Word120 - Word512 - Word120
hashOnce ss a = ss + oneBlock ss a

hash = foldl' hashOnce ss . blockWord32sIn512

convert :: String - [Word8]
convert = map (fromIntegral . ord)

short :: [Word8]
short = convert abc

message :: [Word8]
message = convert abcdbcdecdefdefgefghfghighijhijkijkljklmklmnlmnomnopnopq

performance n =
   (convert . take n . repeat) 'a'

test n = mapM_ (putStrLn . show . hash) [short, message, performance n]

main =
   do progName - getProgName
  args - getArgs
  if length args /= 1
 then putStrLn (Usage:  ++ progName ++  testSize)
 else test (read (args!!0))



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


Re: [Haskell-cafe] Space Leak Help

2007-02-03 Thread kahl
  
  I have re-written SHA1 so that is more idiomatically haskell and it is easy 
  to 
  see how it implements the specification. The only problem is I now have a 
  space leak. I can see where the leak is but I'm less sure what to do about 
  getting rid of it.
  
  Here's the offending function:
  
  pad :: [Word8] - [Word8]
  pad xs =
 xs ++ [0x80] ++ ps ++ lb
 where
l = length xs
pl = (64-(l+9)) `mod` 64
ps = replicate pl 0x00
lb = i2osp 8 (8*l)


I would try something along the following lines (untested):

\begin{spec}
catWithLen xs f = xs ++ f (length xs)
\end{spec}

\begin{code}
catWithLen :: [a] - (Int - [a]) - [a]
catWithLen xs f = h 0 xs
  where
h k [] = f k
h k (x : xs) = case succ k of-- forcing evaluation
 k' - x : h k' xs
\end{code}

\begin{code}
pad :: [Word8] - [Word8]
pad xs = catWithLen xs f
  where
f l = 0x80 : ps lb
  where
 -- we know that |l = length xs|
 pl = (64-(l+9)) `mod` 64
 ps = funPow pl (0x00 :)
 lb = i2osp 8 (8*l)
\end{code}

If you are lucky, then the replicate and the (++lb) in the original code
might be fused by the compiler as an instance of foldr-build
or something related --- check the optimised core code. 

In my variant I changed this to rely on efficient function powering
instead:

\begin{spec}
funPow k f = foldr (.) id $ replicate k f
\end{spec}

\begin{code}
funPow :: Int - (a - a) - (a - a)
funPow n f = case compare n 0 of
LT - error (funPow: negative argument:  ++ show n)
EQ - id
GT - pow n f
  where
pow m g = if m  1
  then let (m',r) = divMod m 2
   g' = g . g
   in if r == 0
  then pow m' g'
  else pow m' g' . g
  else g
\end{code}

(You will probably also consider using Data.Bits
 for (`mod` 64), (8*), and (`divMod` 2).
)


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


Re: [Haskell-cafe] Space Leak Help

2007-02-03 Thread Pepe Iborra

hi Dominic

Explicit recursion works just fine for me and keeps things simple:

pad :: [Word8] - [Word8]
pad xs = pad' xs 0

pad' (x:xs) l = x : pad' xs (succ l)
pad' [] l = [0x80] ++ ps ++ lb
   where
  pl = (64-(l+9)) `mod` 64
  ps = replicate pl 0x00
  lb = i2osp 8 (8*l)


at the cost of (very slightly) hiding data flow.
Seems exactly what you were trying to avoid?

Cheers
pepe


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


Re: [Haskell-cafe] Suggestions for a hReadUntilStr implementation

2007-02-03 Thread Greg Fitzgerald

Hi Matt,


hReadUntilStr - that is, a function that takes a Handle as an input
source, a String to match, and a Num a  as the number of seconds to
wait before returning a (String, Bool) where the String is all the
text read from the Handle until either matching or timing out and the
Bool is true if the input String was matched


This might work for you: http://hpaste.org/289.

It throws an IO exception if hWaitForChar times out, and makes use of lazy
evaluation to schedule all the IO upfront so that grabbing the string prefix
can be done in pure code.

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


[Haskell-cafe] The usage of runghc ?

2007-02-03 Thread keepbal

I tried to install haskell-fastcgi (
http://www.cs.chalmers.se/~bringert/darcs/haskell-fastcgi/ ).


runghc Setup.hs configure  --prefix=$HOME/extra
runghc -I$HOME/extra/include Setup.hs build

Preprocessing library fastcgi-2006.10.9...

FastCGI.hsc:50:21:  error: fcgiapp.h: No such file or directory
compiling Network/FastCGI_hsc_make.c failed
command was: ghc -c Network/FastCGI_hsc_make.c -o Network/FastCGI_hsc_make.o
Setup.hs: got error code while preprocessing: Network.FastCGI


runghc --help

runghc: syntax: runghc [-f GHCPATH] [GHC-ARGS] FILE ARG...

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


Re: [Haskell-cafe] How did you stumble on Haskell?

2007-02-03 Thread Michael Vanier

Lennart,

Now you've made me curious. Which paper is this?  Is it available for download 
anywhere?


Mike

Lennart Augustsson wrote:

On Jan 29, 2007, at 03:01 , Alexy Khrabrov wrote:


How do people stumble on Haskell?


Well, I didn't really stumble on it.  I was at the 1987 meeting
when we decided to define Haskell.

But I stumbled on functional programming in the first place.
I had to learn it because it was part of a course in denotational
semantics.  The language was SASL.  And then I read David Turners
paper on combinators, and I was hooked.

-- Lennart

___
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] How did you stumble on Haskell?

2007-02-03 Thread Lennart Augustsson
A new implementation technique for applicative languages, David A.  
Turner, Software — Practice and Experience, 9:31–49, 1979.


I'm not sure if it's available online.

-- Lennart

On Feb 4, 2007, at 01:14 , Michael Vanier wrote:


Lennart,

Now you've made me curious. Which paper is this?  Is it available  
for download anywhere?


Mike

Lennart Augustsson wrote:

On Jan 29, 2007, at 03:01 , Alexy Khrabrov wrote:

How do people stumble on Haskell?

Well, I didn't really stumble on it.  I was at the 1987 meeting
when we decided to define Haskell.
But I stumbled on functional programming in the first place.
I had to learn it because it was part of a course in denotational
semantics.  The language was SASL.  And then I read David Turners
paper on combinators, and I was hooked.
-- Lennart
___
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] The usage of runghc ?

2007-02-03 Thread Lemmih

On 2/4/07, keepbal [EMAIL PROTECTED] wrote:

I tried to install haskell-fastcgi (
http://www.cs.chalmers.se/~bringert/darcs/haskell-fastcgi/
).

runghc Setup.hs configure  --prefix=$HOME/extra
runghc -I$HOME/extra/include Setup.hs build
Preprocessing library fastcgi-2006.10.9...

FastCGI.hsc:50:21:  error: fcgiapp.h: No such file or directory
compiling Network/FastCGI_hsc_make.c failed
command was: ghc -c Network/FastCGI_hsc_make.c -o Network/FastCGI_hsc_make.o
Setup.hs: got error code while preprocessing: Network.FastCGI


You probably haven't installed fastcgi yet. See http://www.fastcgi.com/

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


Re: [Haskell-cafe] Suggestions for a hReadUntilStr implementation

2007-02-03 Thread Matt Revelle

Thanks for the responses.

Greg, your implementation looks useful but it's a little different
than what I was thinking (my apologies, I wasn't very clear).

In the implementation you posted, the timeout parameter is used to
limit the amount of time spent waiting to read an individual character
- I was hoping to use the timeout as an initial value for a timer that
should start running when hReadUntilStr is evaluated and the function
should finish evaluating when either the timer has run out or when the
string match has been found.

Martin, thanks for the link.

Cheers,
Matt


On 2/3/07, Greg Fitzgerald [EMAIL PROTECTED] wrote:

Hi Matt,

 hReadUntilStr - that is, a function that takes a Handle as an input
 source, a String to match, and a Num a  as the number of seconds to
 wait before returning a (String, Bool) where the String is all the
 text read from the Handle until either matching or timing out and the
 Bool is true if the input String was matched

This might work for you: http://hpaste.org/289 .

It throws an IO exception if hWaitForChar times out, and makes use of lazy
evaluation to schedule all the IO upfront so that grabbing the string prefix
can be done in pure code.

Thanks,
Greg


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


Re: [Haskell-cafe] Alternate instance Show (Maybe a)?

2007-02-03 Thread Sergey Zaharchenko
Hello Yitzchak!

Sat, Feb 03, 2007 at 07:54:17PM +0200 you wrote:

 Show instances are supposed to follow the convention that
 show x is a Haskell expression that recreates x. In other words,
 Show is mainly used for debugging, for simple serialization, and
 for interactive use in a Haskell shell like ghci or hugs.
 
 If you need to create strings from a datatype for some other
 reason, use a different function name. If you need to do it
 for several datatypes, create your own class.

Yes, I think another Show-like class will probably be a better
solution...

Thanks Yitzchak and Bjorn,

-- 
DoubleF
No virus detected in this message. Ehrm, wait a minute...
/kernel: pid 56921 (antivirus), uid 32000: exited on signal 9
Oh yes, no virus:)


pgpKrflZnT8EB.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe