Re: [Haskell-cafe] Fair diagonals (code golf)

2009-11-12 Thread mf-hcafe-15c311f0c

On Wed, Nov 04, 2009 at 07:01:50PM +0100, Sjoerd Visscher wrote:
 To: Haskell Cafe haskell-cafe@haskell.org
 From: Sjoerd Visscher sjo...@w3future.com
 Date: Wed, 4 Nov 2009 19:01:50 +0100
 Subject: Re: [Haskell-cafe] Fair diagonals (code golf)
 
 The code by Twan can be reduced to this:

 diagN = concat . foldr f [[[]]]

 f :: [a] - [[[a]]] - [[[a]]]
 f xs ys = foldr (g ys) [] xs

 g :: [[[a]]] - a - [[[a]]] - [[[a]]]
 g ys x xs = merge (map (map (x:)) ys) ([] : xs)

 merge :: [[a]] - [[a]] - [[a]]
 merge [] ys = ys
 merge xs [] = xs
 merge (x:xs) (y:ys) = (x++y) : merge xs ys

 But my feeling is that this can still be simplified further. Or at least 
 refactored so it is clear what actually is going on!

i wrote another solution:


diag2 xs ys = join . takeWhile (not . null) . map f $ [1..]
where
  f i = zip xs' ys'
  where
xs' = take i $ drop (i - length ys') xs
ys' = reverse $ take i ys

diag [] = []
diag [q] = [q]
diag qs = foldr f (map (:[]) $ last qs) (init qs)
where
  f q' = map (uncurry (++)) . diag2 (map (:[]) q')


diag is the recursion step over the dimensions; diag2 is the base case
with two dimensions.  i can see that it's less efficient on
(partially) finite inputs, since i keep dropping increasing prefixes
of xs and ys in the local f in diag2), and there are probably other
issues.  but it was fun staring at this problem for a while.  :)

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


Re: [Haskell-cafe] Merging modules

2009-10-16 Thread mf-hcafe-15c311f0c
On Fri, Oct 16, 2009 at 11:42:22AM +0100, pat browne wrote:
 To: haskell-cafe@haskell.org
 From: pat browne patrick.bro...@comp.dit.ie
 Date: Fri, 16 Oct 2009 11:42:22 +0100
 Subject: [Haskell-cafe] Merging modules
 
 Hi,
 I want to establish the strengths and weakness of the Haskell module
 system for the ontology merging task (I know it was not designed for
 this!). I wish to make a new module (MERGEDONTOLOGY) from three input
 modules one of which is common to the other two.
 The desired merge should contain the following data types:
  Woman FinancialBank HumanBeing RiverBank
 Which are all identifiable without any qualifying module names.
 
 Below is the detailed requirement and my first attempt at this task in
 Haskell. I would be grateful for any information on how to merge these
 modules giving a set of unique unqualified types (i.e. without reference
 to their originating modules).
 
 Regards,
 Pat
 
 
 
 
 
 Informal Specification
 
 
 The diagram and text below explain the requirement
 
MERGEDONTOLOGY
   { Woman, RiverBank, FinancialBank, HumanBeing}
 /\  /\
/ \
   /\
  /  \
 / \
/   \
   / \
 
 ONTOLOGY1  ONTOLOGY2
 {Woman, Bank, Person}   {Woman, Bank, Human}
  /\  /\
   \  /
 \   /
  \ /
\ /
 \  /
  \   /
   \ /
 {Woman ,  Person}
COMMMON
 
 This example includes both synonyms and homonyms.
 1)The Woman sort (or data type) should be the same in all modules, there
 is only one Woman sort and it is named as such in each module. Hence
 there should be only one MERGEDONTOLOGY.Woman.
 
 2)There is only one sort MERGEDONTOLOGY.HumanBeing, but there are 3
 synonyms for it called ONTOLOGY2.Human, ONTOLOGY1.Person, and
 COMMON.Person. The last sentence considers ONTOLOGY1.Person and
 COMMON.Person as synonyms; they have different qualifiers but the
 intention is that they represnt the same thing. Hence should be mapped
 to same MERGEDONTOLOGY.HumanBeing. To do this (in Maude) COMMON.Person
 was  renamed to ONTOLOGY2.Human which in turn was renamed to
 MERGEDONTOLOGY.HumanBeing.
 
 3)The homonyms are ONTOLOGY1.Bank and ONTOLOGY2.Bank should become
 distinct sorts MERGEDONTOLOGY.RiverBank and
 MERGEDONTOLOGY.FinancialBank in the final ontology at the top of the
 diagram.
 
 
 
 My first attemt at merging using Haskell modules
 =
 module COMMON where
  data  Woman = WomanC
  data Person  = PersonC
 
 
 
 module  ONTOLOGY1 where
  import COMMON
  data Bank = BankC
 
 
 module ONTOLOGY2 where
  import COMMON
  data Bank = BankC
 
 
 
 module MERGEDONTOLOGY where
   import ONTOLOGY1
   import ONTOLOGY2
 
 If I use qualified names all the constructors are interpreted correctly
  MERGEDONTOLOGY :t COMMON.WomanC
  COMMON.WomanC :: COMMON.Woman
  MERGEDONTOLOGY :t COMMON.PersonC
  COMMON.PersonC :: COMMON.Person
  MERGEDONTOLOGY :t ONTOLOGY2.BankC
  ONTOLOGY2.BankC :: ONTOLOGY2.Bank
  MERGEDONTOLOGY :t ONTOLOGY1.BankC
  ONTOLOGY1.BankC :: ONTOLOGY1.Bank
  MERGEDONTOLOGY :t COMMON.Woman
 
 However, I wish that these types and constructors be fully defined in
 the context of the  MERGEDONTOLOGY. I have tried type synonyms and newtypes.
   type RiverBank = ONTOLOGY1.Bank
   type FinancialBank = ONTOLOGY2.Bank
   newtype RiverBank = BankC Int
 I have not explored import modes or qualified imports.

The way you import ONTOLOGY* and COMMON without qualified, you can
use any name that you import without qualifier, as long as the name is
unique over all imported modules.

Where names would conflict, you can list the names to be imported
explicitly, and omit the names that cause conflicts:

import ONTOLOGY1 (Woman (..), Person (..))

or list the names to be omitted:

import ONTOLOGY1 hiding (Bank (..))

In your example, you want both banks (from both ontologies), and name
them differently.  If this is a common thing in your application,
perhaps you want to use type classes instead of plain data types, or
one of the other many extensions 

Re: [Haskell-cafe] Merging modules

2009-10-16 Thread mf-hcafe-15c311f0c

On Fri, Oct 16, 2009 at 12:56:30PM +0100, pat browne wrote:
 To: haskell-cafe@haskell.org
 From: pat browne patrick.bro...@comp.dit.ie
 Date: Fri, 16 Oct 2009 12:56:30 +0100
 Subject: Re: [Haskell-cafe] Merging modules
 
 
 
  This is all pretty basic stuff.  Not sure any of it is very helpful.
  (Why do you want to spread an ontology over several Haskell modules?)
  
  
  -matthias
 
 Yes it is very helpful, I have limited time to study Haskell.

excellent (:

 The reason for spreading the information over modules is to simulate
 actual ontologies and the mappings to other ontologies. My next step is,
 as you suggested, to use type classes. My overall thesis is the study of
  current algebraic specification and programming techniques.

another thing you may want to know about is template haskell (what
haskellers use instead of lisp macros).  instead of creating trivial
type instances for hundrets or thousands of type classes, you can call
one macro for each class / data pair that unfolds into both.  this may
make your source code a lot more concise and elegant.

please post the outcome of this if you can find the time.

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


Re: [Haskell-cafe] statistics package and randomness

2009-10-12 Thread mf-hcafe-15c311f0c


i'll try a very non-technical explanation that has worked for me so
far.  (is it correct?  does it make sense?)

IO and ST are quite similar.  the difference is that whereas IO gives
you a concept of time in the world surrounding your code, ST lets you
create a little bubble inside your code in which you can maintain
state, while the bubble as a whole acts all pure and lazy.  for
example, if you want to implement an algorithm that writes to and
reads from a matrix, you use ST: you want to control the order in
which you read from and write to it, but not the order in which access
events to that data structure mixes with user interaction events.

-matthias



On Mon, Oct 12, 2009 at 12:25:43AM -0700, Michael Mossey wrote:
 To: Haskell Cafe Haskell-Cafe@haskell.org
 Cc: 
 From: Michael Mossey m...@alumni.caltech.edu
 Date: Mon, 12 Oct 2009 00:25:43 -0700
 Subject: [Haskell-cafe] statistics package and randomness
 
 I'm trying to learn how to use randomness in Haskell and it seems very  
 non-straightforward and complex. I could do a lot of things using 'split' 
 from System.Random, but apparently it's broken. There is the statistics  
 package here:

 http://hackage.haskell.org/package/statistics

 Is this a better solution?

 It uses the ST monad in the RandomVariate module. Can someone point me to 
 a tutorial explaining ST, and/or a tutorial in the RandomVariate module?

 Pseudorandomness seems like one case where it would just be a hell of a 
 lot simpler to have a global generator--never split the state. Is the ST 
 monad some way to accomplish this?

 Thanks,
 Mike


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


 ** ACCEPT: CRM114 PASS osb unique microgroom Matcher ** CLASSIFY 
 succeeds; success probability: 1.  pR: 5.5394
 Best match to file #0 (nonspam.css) prob: 1.  pR: 5.5394  Total 
 features in input file: 2960
 #0 (nonspam.css): features: 758386, hits: 2888631, prob: 1.00e+00, pR:   
 5.54 #1 (spam.css): features: 1683715, hits: 3150692, prob: 2.89e-06, pR: 
  -5.54 

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


Re: [Haskell-cafe] How do I get this done in constant mem?

2009-10-11 Thread mf-hcafe-15c311f0c

On Sat, Oct 10, 2009 at 11:11:24PM +0200, Daniel Fischer wrote:
 To: haskell-cafe@haskell.org
 From: Daniel Fischer daniel.is.fisc...@web.de
 Date: Sat, 10 Oct 2009 23:11:24 +0200
 Subject: Re: [Haskell-cafe] How do I get this done in constant mem?
 
 Am Samstag 10 Oktober 2009 22:14:38 schrieb mf-hcafe-15c311...@etc-network.de:
  On Sat, Oct 10, 2009 at 09:33:52AM -0700, Thomas Hartman wrote:
   To: Luke Palmer lrpal...@gmail.com
   Cc: mf-hcafe-15c311...@etc-network.de, haskell-cafe@haskell.org
   From: Thomas Hartman tphya...@gmail.com
   Date: Sat, 10 Oct 2009 09:33:52 -0700
   Subject: Re: [Haskell-cafe] How do I get this done in constant mem?
  
Yes, you should not do this in IO.  That requires the entire
computation to finish before the result can be used.
  
   Not really the entire computation though... whnf, no?
 
  In that example, yes.  But readFile takes the entire file into a
  strict String before it gives you the first Char, right?  (Sorry again
  for my misleading code simplification.)
 
 No, readFile reads the file lazily.

hm?  oh, you are right, now that i fixed all the other problems in my
code readFile isn't a problem any more either...  (-:

(but then how does it know when to close the handle?  gotta go read
the code i guess.)

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


Re: [Haskell-cafe] How do I get this done in constant mem?

2009-10-10 Thread mf-hcafe-15c311f0c

On Fri, Oct 09, 2009 at 05:48:15PM -0600, Luke Palmer wrote:
 To: mf-hcafe-15c311...@etc-network.de
 Cc: 
 From: Luke Palmer lrpal...@gmail.com
 Date: Fri, 9 Oct 2009 17:48:15 -0600
 Subject: Re: [Haskell-cafe] How do I get this done in constant mem?
 
 On Fri, Oct 9, 2009 at 2:05 PM,  mf-hcafe-15c311...@etc-network.de wrote:
  Hi all,
 
  I think there is something about my use of the IO monad that bites me,
  but I am bored of staring at the code, so here you g.  The code goes
  through a list of records and collects the maximum in each record
  position.
 
 
  -- test.hs
  import Random
  import System.Environment (getArgs)
  import System.IO (putStr)
 
  samples :: Int - Int - IO [[Double]]
  samples i j = sequence . replicate i . sequence . replicate j $ randomRIO 
  (0, 1000 ** 3)
 
 Yes, you should not do this in IO.  That requires the entire
 computation to finish before the result can be used.  This computation
 should be pure and lazy.

Yeah.  I also got an excellent reason via private mail why sequence
has to be strict:

sequence [Maybe 3, Maybe 4, Nothing]  = Nothing
sequence [Maybe 3, Maybe 4]   = Just [3, 4]

  maxima :: [[Double]] - [Double]
  maxima samples@(_:_) = foldr (\ x y - map (uncurry max) $ zip x y) (head 
  samples) (tail samples)
 
 FWIW, This function has a beautiful alternate definition:
 
 maxima :: [[Double]] - [Double]
 maxima = map maximum . transpose

Beautiful indeed!  But see below.

To be honest, I don't really roll dice, but I am reading from a file.
I just thought that randomRIO would be more concise, but now the
discussion has gone totally in that direction.  Sorry...  (-: reading
the random number code is more fun, though!

Anyhow, I fixed my example to do lazy file processing where before I
used readFile (which has to be strict, as I can see now).  First, I
generate a file with the samples, and then I read that file back (this
is the phase I'm interested in, since my real data is not really
random numbers).


import List
import Monad
import Random
import System.Environment
import System.IO

samples :: Int - Int - IO [[Int]]
samples i j = sequence . replicate i . sequence . replicate j $ randomRIO (0, 
1000 * 1000 * 1000)

maxima :: [[Int]] - [Int]
maxima samples@(_:_) = foldr (\ x y - map (uncurry max) $ zip x y) (head 
samples) (tail samples)

lazyProcess :: ([[Int]] - a) - FilePath - IO a
lazyProcess f fileName =
do
  h - openFile fileName ReadMode
  v - fmap (f . map read . lines) $ hGetContents h
  v `seq` hClose h
  return v

mkSamples = do
  args - getArgs
  x - samples (read (head args)) 5
  putStr . (++ \n) . join . intersperse \n . map show $ x

-- main = mkSamples
-- ghc --make -O9 test.hs -o test  ./test 1  test.data

main = lazyProcess length test.data = putStr . show


lazyProcess (What would be a better name?  foldSampleFile perhaps?) is
where the IO happens, but the computation is located in a pure
function.  And yet, only those lines are read that are relevant, and
GC on previous lines is allows if the pure function allows it.

This program has constant memory usage.  Unfortunately, if I replace
the length function with implementation of maxima, it explodes again.
I tried a few things, such as

maxima'3 :: [[Int]] - [Int]
maxima'3 (h:t) = foldr (\ x y - let v = map (uncurry max) $ zip x y in sum v 
`seq` v) h t

with no luck so far.  Tricky business, that!  But much more curiously,
if I replace maxima'3 in main with this

maxima'4 :: [[Int]] - [Int]
maxima'4 = map maximum . transpose

(with explicit type signature in both definitions), I get a 'no parse'
error from Prelude.read.  maxima'3 with the same file gives me a
result.  How can there be a difference if the type signatures are
identical?!

Probably something about don't use Prelude.read :-)?  I have to play
with this some more...



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


Re: [Haskell-cafe] How do I get this done in constant mem?

2009-10-10 Thread mf-hcafe-15c311f0c
On Sat, Oct 10, 2009 at 09:33:52AM -0700, Thomas Hartman wrote:
 To: Luke Palmer lrpal...@gmail.com
 Cc: mf-hcafe-15c311...@etc-network.de, haskell-cafe@haskell.org
 From: Thomas Hartman tphya...@gmail.com
 Date: Sat, 10 Oct 2009 09:33:52 -0700
 Subject: Re: [Haskell-cafe] How do I get this done in constant mem?
 
  Yes, you should not do this in IO.  That requires the entire
  computation to finish before the result can be used.
 
 Not really the entire computation though... whnf, no?

In that example, yes.  But readFile takes the entire file into a
strict String before it gives you the first Char, right?  (Sorry again
for my misleading code simplification.)

 main = do
   let thunks :: IO [Int]
   thunks = (sequence . replicate (10^6) $ (randomRIO (0,10^9)))
   putStrLn . show . head = thunks -- prints
   putStrLn . show . last = thunks -- overflows

Meaning that the entire list needs to be kept?  Is there a reason
(other than it's easier to implement and it's legal :-) why the
elements that have been traversed by last can't be garbage
collected?



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


[Haskell-cafe] How do I get this done in constant mem?

2009-10-09 Thread mf-hcafe-15c311f0c


Hi all,

I think there is something about my use of the IO monad that bites me,
but I am bored of staring at the code, so here you g.  The code goes
through a list of records and collects the maximum in each record
position.


-- test.hs
import Random
import System.Environment (getArgs)
import System.IO (putStr)

samples :: Int - Int - IO [[Double]]
samples i j = sequence . replicate i . sequence . replicate j $ randomRIO (0, 
1000 ** 3)

maxima :: [[Double]] - [Double]
maxima samples@(_:_) = foldr (\ x y - map (uncurry max) $ zip x y) (head 
samples) (tail samples)

main = do
  args - getArgs
  x - samples (read (head args)) 5
  putStr . (++ \n) . show $ maxima x


I would expect this to take constant memory (foldr as well as foldl),
but this is what happens:


$ ghc -prof --make -O9 -o test test.hs
[1 of 1] Compiling Main ( test.hs, test.o )
Linking test ...
$ ./test 100 +RTS -p
[9.881155955344708e8,9.910336352165401e8,9.71000686630374e8,9.968532576451201e8,9.996200333115692e8]
$ grep 'total alloc' test.prof 
total alloc = 744,180 bytes  (excludes profiling overheads)
$ ./test 1 +RTS -p
[9.996199711457872e8,9.998928358545277e8,9.99960283632381e8,9.999707142123885e8,9.998952151508758e8]
$ grep 'total alloc' test.prof 
total alloc =  64,777,692 bytes  (excludes profiling overheads)
$ ./test 100 +RTS -p
Stack space overflow: current size 8388608 bytes.
Use `+RTS -Ksize' to increase it.
$ 


so...

does sequence somehow force the entire list of monads into evaluation
before the head of the result list can be used?  what can i do to
implement this in constant memory?

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


Re: [Haskell-cafe] Network.Curl and posting XML data

2009-10-07 Thread mf-hcafe-15c311f0c


Hi Erik,

I am not aware of any SSL implementation in haskell either (even
though I think it should go not into HTTP but into Crypto (which is a
neat piece of code, but needs a lot more work)).

I can think of two quick solutions if you need your Haskell code to
use an SSL link: run stunnel.org and make your application connect to
that, or write a Haskell wrapper around openssl.org.

As for the latter, I don't know your requirements and resources so
this may be possible, but from what i've seen of openssl i wouldn't
want to have to do that.

good luck,
matthias



On Wed, Oct 07, 2009 at 02:38:05PM +1100, Erik de Castro Lopo wrote:
 To: haskell-cafe@haskell.org
 From: Erik de Castro Lopo mle...@mega-nerd.com
 Date: Wed, 7 Oct 2009 14:38:05 +1100
 Subject: Re: [Haskell-cafe] Network.Curl and posting XML data
 
 Dmitry Olshansky wrote:
 
  Hi, Erik,
  
  Did you try Network.HTTP? Is it not enough?
 
 Apparently not.
 
 Now I need to do a post to a HTTPS server and Network.HTTP does
 not seem to support HTTPS. Is that really right?
 
 Erik
 -- 
 --
 Erik de Castro Lopo
 http://www.mega-nerd.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Network.Curl and posting XML data

2009-10-07 Thread mf-hcafe-15c311f0c

I stand corrected.  The answer was 'cabal install HsOpenSSL'.


On Wed, Oct 07, 2009 at 09:37:38PM +1100, Erik de Castro Lopo wrote:
 To: haskell-cafe@haskell.org
 From: Erik de Castro Lopo mle...@mega-nerd.com
 Date: Wed, 7 Oct 2009 21:37:38 +1100
 Subject: Re: [Haskell-cafe] Network.Curl and posting XML data
 
 mf-hcafe-15c311...@etc-network.de wrote:
 
  I am not aware of any SSL implementation in haskell either (even
 
 I really find this rather surprising. Ocaml has a very decent wrapper
 around Openssl that works rather well so it can't be that hard.

Does this mean something that has been done in Ocaml can't be tedious
and/or difficult?

I'm just saying that openssl has a very complex (and IMHO not very
efficient) API, and that I am not at all certain whether writing a
wrapper is better for your project than adding the functionality you
need to Crypto.  But I may be wrong.


  though I think it should go not into HTTP but into Crypto (which is a
  neat piece of code, but needs a lot more work)).
 
 But why shouldn't it should go into Network.HTTP? All I want to do
 is a HTTP POST of text/xml data to a HTTPS server and retrieve the
 text/xml data response and the HTTP response code. Whether that 
 URL is HTTP vs HTTPS shouldn't matter.
 
 With a sane API I should just be able to change from a HTTP url to 
 a HTTPS url and have it JustWork (tm). To have to use a different
 library depending on whether I'm doing http vs https is just
 horrible.

As Magnus has pointed out (thanks), that's not what I mean.  I am just
saying that hacking SSL into an HTTP library is wrong, since SSL is
something different.  For instance, it is also commonly used for POP,
IMAP, SMTP, and generic TCP tunneling.


  I can think of two quick solutions if you need your Haskell code to
  use an SSL link: run stunnel.org
 
 Sorry, thats way too cludgy for my application.
 
  and make your application connect to
  that, or write a Haskell wrapper around openssl.org.
 
 I've used openssl directly from C and C++ so  I know its doable, but
 I consider openssl a real blemish on the FOSS world.

agreed!


 There is however this:
 

 http://hackage.haskell.org/packages/archive/HsOpenSSL/0.6.5/doc/html/OpenSSL-Session.html

I really should look at hackage next time I am about to claim
something doesn't exist.  I just assumed you already had.  :)

Anyway, until somebody finds the time to put all these little related
libraries together, this is probably what you want to use.


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


Re: [Haskell-cafe] How to generate random string?

2009-09-20 Thread mf-hcafe-15c311f0c

does this compile at all?  i don't think i understand the first line.
anyway, a few hints:

  - if you want to have all numbers between 0..n in your output for
some n, just in random order, google for permutation.

  - perhaps you can generate the output in an ordered fashion first,
eg. into an array, and then shuffle the list by plucking elements
from it at random into a new list.

  - do not use unsafePerformIO.  it may reduce the entropy
(randomness) of the results, but even if it doesn't, the code is
prettier without.

good luck!  if you get stuck again, just post more code.
matthias


On Fri, Sep 18, 2009 at 10:14:53AM -0700, Snouser wrote:
 To: haskell-cafe@haskell.org
 From: Snouser linusolean...@gmail.com
 Date: Fri, 18 Sep 2009 10:14:53 -0700 (PDT)
 Subject: Re: [Haskell-cafe] How to generate random string?
 
 
 
 
 Snouser wrote:
  
  I need to generate a random string from 1 to 30.
  
  This is the parts I've done so far.
  
  unikString xs | let x = unsafePerformIO (randomRIO (1,30)) elem x xs = x :
  unikString xs
| otherwise = unikString xs
  
  How do I proceed?
  
  I need the string/list to look like this:
  
  [1,9,3,6,2] et.c with only unik numbers.
  
  Thanks!
  
 
 I wasnt added to the mailinglist, but now I'm.
 
 
 -- 
 View this message in context: 
 http://www.nabble.com/How-to-generate-random-string--tp25512293p25512298.html
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
  
  ** ACCEPT: CRM114 PASS osb unique microgroom Matcher ** 
 CLASSIFY succeeds; success probability: 1.  pR: 6.3668
 Best match to file #0 (nonspam.css) prob: 1.  pR: 6.3668  
 Total features in input file: 2688
 #0 (nonspam.css): features: 758386, hits: 2881904, prob: 1.00e+00, pR:   6.37 
 #1 (spam.css): features: 1686754, hits: 3078784, prob: 4.30e-07, pR:  -6.37 
  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] trouble compiling Crypto-4.2.0 / trouble with cabal

2009-09-13 Thread mf-hcafe-15c311f0c


Hi,

Cabal is still fighting me all the time.  Its latest move is to be
oblivious of some of the installed packages:

$ cabal unpack crypto
Unpacking Crypto-4.2.0...
$ cd Crypto-4.2.0/
$ runghc ./Setup.hs configure --prefix=/tmp2/
Configuring Crypto-4.2.0...
Setup.hs: At least the following dependencies are missing:
HUnit -any, QuickCheck -any
$ ghc-pkg list | grep -i -e '\(cabal\|hunit\)'
Cabal-1.6.0.3, array-0.2.0.0, base-3.0.3.1, base-4.1.0.0,
HTTP-4000.0.8, HUnit-1.2.2.0, ObjectName-1.0.0.0, OpenGL-2.3.0.0,

My ghc version is 6.10.4.20090719.  (Perhaps I should go get myself a
more stable version?)

How does Cabal find its packages other than by ghc-pkg?  I read the
documentation, and did a quick search, but came up empty-handed.

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


[Haskell-cafe] [Solved] Re: trouble compiling Crypto-4.2.0 / trouble with cabal

2009-09-13 Thread mf-hcafe-15c311f0c

works, thanks!  (:

actually, what i did in the end is this (installing everything for my
user locally):

runghc ./Setup.hs configure --user --prefix=/tmp2/
runghc ./Setup.hs build
...

(I first did the 'cabal install crypto', but for ghc-6.10.4 that
didn't work.  will start debugging now.)

matthias


On Sun, Sep 13, 2009 at 11:26:50AM -0700, Thomas DuBuisson wrote:
 To: mf-hcafe-15c311...@etc-network.de
 Cc: haskell-cafe@haskell.org
 From: Thomas DuBuisson thomas.dubuis...@gmail.com
 Date: Sun, 13 Sep 2009 11:26:50 -0700
 Subject: Re: [Haskell-cafe] trouble compiling Crypto-4.2.0 / trouble with 
   cabal
 
 Cabal, the library you are using when manuallying running Setup.hs,
 assumes you are doing a global installation and will ignore locally
 installed libraries (iirc).  If you do 'cabal install crypto',
 cabal-install defaults to user installs and will use the user
 libraries.
 
 Thomas
 
 On Sun, Sep 13, 2009 at 10:54 AM,  mf-hcafe-15c311...@etc-network.de wrote:
 
 
  Hi,
 
  Cabal is still fighting me all the time.  Its latest move is to be
  oblivious of some of the installed packages:
 
  $ cabal unpack crypto
  Unpacking Crypto-4.2.0...
  $ cd Crypto-4.2.0/
  $ runghc ./Setup.hs configure --prefix=/tmp2/
  Configuring Crypto-4.2.0...
  Setup.hs: At least the following dependencies are missing:
  HUnit -any, QuickCheck -any
  $ ghc-pkg list | grep -i -e '\(cabal\|hunit\)'
     Cabal-1.6.0.3, array-0.2.0.0, base-3.0.3.1, base-4.1.0.0,
     HTTP-4000.0.8, HUnit-1.2.2.0, ObjectName-1.0.0.0, OpenGL-2.3.0.0,
 
  My ghc version is 6.10.4.20090719.  (Perhaps I should go get myself a
  more stable version?)
 
  How does Cabal find its packages other than by ghc-pkg?  I read the
  documentation, and did a quick search, but came up empty-handed.
 
  thanks,
  matthias
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
 
  ** ACCEPT: CRM114 PASS osb unique microgroom Matcher **
 CLASSIFY succeeds; success probability: 1.  pR: 9.9721
 Best match to file #0 (nonspam.css) prob: 1.  pR: 9.9721
 Total features in input file: 3072
 #0 (nonspam.css): features: 758386, hits: 2510804, prob: 1.00e+00, pR:   9.97
 #1 (spam.css): features: 1686754, hits: 2531046, prob: 1.07e-10, pR:  -9.97
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[Haskell-cafe] [2]: memoization

2009-09-10 Thread mf-hcafe-15c311f0c

On Thu, Sep 10, 2009 at 05:23:26AM -0700, staafmeister wrote:
 To: haskell-cafe@haskell.org
 From: staafmeister g.c.stave...@uu.nl
 Date: Thu, 10 Sep 2009 05:23:26 -0700 (PDT)
 Subject: Re: Re[Haskell-cafe] [2]: memoization
 
 
 
 Hi Bulat,
 
 
 Bulat Ziganshin-2 wrote:
  
  Hello staafmeister,
  
  Thursday, September 10, 2009, 3:54:34 PM, you wrote:
  
  What do you think about such a function? This function is
  
  a bit of refactoring
  
  -- global variable in haskell way
  cache = unsafePerformIO $ newIORef M.empty
  
  memo f x = unsafePerformIO$ do
 m - readIORef cache
 case M.lookup x m of
   Just y - return y
   Nothing - do let res = f x
 writeIORef cache $ M.insert x res m
 return res
  
  memo2 = curry . memo . uncurry
  
 
 This doesn't work and is exactly what I'm afraid the compiler is going to
 do. Cache needs to
 be associated with the function f.
 
 Otherwise one would get conflicts

then make the cache object store functions together with values.


cache = unsafePerformIO $ newIORef M.empty

memo f x = unsafePerformIO$ do
   m - readIORef cache
   case M.lookup (mkKey f, x) m of
 Just y - return y
 Nothing - do let res = f x
   writeIORef cache $ M.insert (mkKey f, x) 
res m
   return res

memo2 = curry . memo . uncurry

This leaves mkKey.  Since functions are neither Ord nor Show, you'd
have to hack something together yourself.  Perhaps an explicit
argument to memo?

memo :: (Ord a) = String - (a - b) - a - IO b
memo fname f x = unsafePerformIO$ do
   m - readIORef cache
   case M.lookup (fname, x) m of
 Just y - return y
 Nothing - do let res = f x
   writeIORef cache $ M.insert (fname, x) 
res m
   return res

there is probably a better and more elegant solution, but this should
at least work.  right?


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


Re: [Haskell-cafe] Re: ForeignFunPtr

2009-09-08 Thread mf-hcafe-15c311f0c


You are right, I forgot about callbacks.  freeHaskellFunPtr is only
for Haskell functions packaged for usage by the foreign code.  Example
from the FFI specification, Section 5.4.2:

type Compare = Int - Int - Bool
foreign import ccall wrapper
  mkCompare :: Compare - IO (FunPtr Compare)

If you, say,

x = mkCompare ()

and at some point decide x is not needed in your foreign code any
more, it has to be freed by hand.

This is the only case in which you are allowed to use
freeHaskellFunPtr.  The (much less interesting) case that I was
thinking about, where FunPtr is used for foreign C functions, usually
requires no finalization.

ForeignPtr is used for foreign objects used by Haskell.  The garbage
collector (gc) can decide whether the object is still in use and, if
it's not, finalize it.

A Haskell function wrapped in a FunPtr is used in the foreign world.
Haskell gc cannot be made responsible for finalizing it.  In fact,
(unless the foreign world has some gc of its own) there is no way for
any compiler of deciding when to finalize at all.  The programmer
needs to decide this by calling freeHaskellFunPtr, just like she needs
to decide when to free mallocked memory in C.

Does that make more sense?  Please kick me again if you are still not
buying it.  :-)

cheers,
matthias



On Sun, Sep 06, 2009 at 02:53:52PM -0300, Maur??cio CA wrote:
 To: haskell-cafe@haskell.org
 From: Maur??cio CA mauricio.antu...@gmail.com
 Date: Sun, 06 Sep 2009 14:53:52 -0300
 Subject: [Haskell-cafe] Re: ForeignFunPtr
 
 Isn't freeHaskellFunPtr a required finalization procedure?

 Maurício

 the purpose of ForeignPtr is to attach a finalization procedure to the
 object behind the pointer.  for example, you can have close called
 aimplicitly whenever the garbage collector finds you don't need a file
 handle any more.  function pointers do not need finalization.


 We have ForeignPtr. Why isn't there a
 corresponding ForeignFunPtr?


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


 ** ACCEPT: CRM114 PASS osb unique microgroom Matcher ** CLASSIFY 
 succeeds; success probability: 1.  pR: 5.6531
 Best match to file #0 (nonspam.css) prob: 1.  pR: 5.6531  Total 
 features in input file: 2752
 #0 (nonspam.css): features: 758386, hits: 2838587, prob: 1.00e+00, pR:   
 5.65 #1 (spam.css): features: 1686574, hits: 3088399, prob: 2.22e-06, pR: 
  -5.65 

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


Re: [Haskell-cafe] ForeignFunPtr

2009-09-06 Thread mf-hcafe-15c311f0c

the purpose of ForeignPtr is to attach a finalization procedure to the
object behind the pointer.  for example, you can have close called
aimplicitly whenever the garbage collector finds you don't need a file
handle any more.  function pointers do not need finalization.

cheers,
matthias


On Sat, Sep 05, 2009 at 07:51:59PM -0300, Maur??cio CA wrote:
 To: haskell-cafe@haskell.org
 From: Maur??cio CA mauricio.antu...@gmail.com
 Date: Sat, 05 Sep 2009 19:51:59 -0300
 Subject: [Haskell-cafe] ForeignFunPtr
 
 Hi,

 We have ForeignPtr. Why isn't there a
 corresponding ForeignFunPtr?


 Thanks,
 Maurício

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


 ** ACCEPT: CRM114 PASS osb unique microgroom Matcher ** CLASSIFY 
 succeeds; success probability: 0.  pR: 4.1765
 Best match to file #0 (nonspam.css) prob: 0.  pR: 4.1765  Total 
 features in input file: 2256
 #0 (nonspam.css): features: 758386, hits: 2818973, prob: 1.00e+00, pR:   
 4.18 #1 (spam.css): features: 1686574, hits: 3077879, prob: 6.66e-05, pR: 
  -4.18 

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


[Haskell-cafe] greencard error message

2009-09-04 Thread mf-hcafe-15c311f0c

greetings,

greencard is confusing me: I copied an example from the command line
and was hoping to look at some generated Haskell code to understand
what's going on, but got this instead:

| $ cat M1.gc
| module M1 where
| %enum PosixError Int [EACCES, ENOENT]
| $ greencard M1.gc
| greencard: user error (unknown, line unknown:
|   Don't know how to unmarshall (int res1)
| 
| unknown, line unknown:
|   Don't know how to unmarshall (int res1)
| 
| )

(is there any live code out there that i could use as an example to
study?  most of the links from haskell.org/greencard are dead.
anybody agree to earlier comments that greencard is obsolete?  i
really like it so far and would be glad to hear otherwise.)

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


Re: [Haskell-cafe] How to preload the module of my own

2009-09-04 Thread mf-hcafe-15c311f0c

echo ':load ~/money/Money.hs'  ~/.ghci

works for me.  this adds a line to the startup script that loads a
file that is not in any package.  if this module loads other modules,
you may need to play with ':cd' in addition to ':load'.

hope this helps,
matthias


On Fri, Sep 04, 2009 at 06:14:50PM -0700, Alexander Dunlap wrote:
 To: zaxis z_a...@163.com, Haskell Cafe haskell-cafe@haskell.org
 Cc: 
 From: Alexander Dunlap alexander.dun...@gmail.com
 Date: Fri, 4 Sep 2009 18:14:50 -0700
 Subject: Re: [Haskell-cafe] How to preload the module of my own
 
 On Fri, Sep 4, 2009 at 6:08 PM, zaxisz_a...@163.com wrote:
 
  I want to preload the module automatically when starting ghci. The module
  located in ~/work directory contains some functions i use everyday.
 
  Now i use an alias: alias ghci='ghci -i ~/money/Money.hs' which works fine.
  However i feel there maybe are more elegant way.
 
  thanks!
 
 
 If the module is part of a package you can put 'import NameOfModule'
 in your ~/.ghc/.ghci file. That file contains commands that are run
 when ghci starts. I'm not sure if you can load a module that isn't
 installed.
 
 Alex
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
  
  ** ACCEPT: CRM114 PASS osb unique microgroom Matcher ** 
 CLASSIFY succeeds; success probability: 1.  pR: 11.8869
 Best match to file #0 (nonspam.css) prob: 1.  pR: 11.8869  
 Total features in input file: 2936
 #0 (nonspam.css): features: 758386, hits: 2835097, prob: 1.00e+00, pR:  11.89 
 #1 (spam.css): features: 1686574, hits: 2959087, prob: 1.30e-12, pR: -11.89 
  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] cannot build greencard

2009-09-02 Thread mf-hcafe-15c311f0c


hi,

i am stuck with a linker error in greencard, and haven't found
anything online, so i am addressing you for fresh ideas.  as soon as i
get this sorted out, i will try to turn the answer into a patch that
you can consider for the next release.

SYMPTOMS: greencard 3.0.3 and 3.01 do not compile with ghc-6.8 (debian
lenny package) and 6.10 (darcs copy, checked out yesterday).  here is
what happens:


4 (0) 19:27:19 m...@yoyo:/tmp2 $ tar xvpzf greencard-3.0.3.tar.gz 
greencard-3.0.3/
greencard-3.0.3/ANNOUNCE
greencard-3.0.3/dist/
greencard-3.0.3/dist/build/
greencard-3.0.3/dist/build/greencard/
greencard-3.0.3/dist/build/greencard/greencard-tmp/
greencard-3.0.3/dist/build/greencard/greencard-tmp/Parse.hs
greencard-3.0.3/examples/
greencard-3.0.3/examples/Gdbm/
greencard-3.0.3/examples/Gdbm/diffs
greencard-3.0.3/examples/Gdbm/Gdbm.gc
greencard-3.0.3/examples/Gdbm/gdbmplus.h
greencard-3.0.3/examples/Gdbm/Main.hs
greencard-3.0.3/examples/Gdbm/Makefile
greencard-3.0.3/examples/Gdbm/README
greencard-3.0.3/examples/Makefile
greencard-3.0.3/examples/world/
greencard-3.0.3/examples/world/Main.hs
greencard-3.0.3/examples/world/Makedefs.ghc
greencard-3.0.3/examples/world/Makedeps
greencard-3.0.3/examples/world/Makefile.ghc-linux
greencard-3.0.3/examples/world/Makefile.ghc-win32
greencard-3.0.3/examples/world/Makefile.hugs-linux
greencard-3.0.3/examples/world/Makefile.hugs-win32
greencard-3.0.3/examples/world/README.txt
greencard-3.0.3/examples/world/World.gc
greencard-3.0.3/greencard.cabal
greencard-3.0.3/INSTALL
greencard-3.0.3/lib/
greencard-3.0.3/lib/Foreign/
greencard-3.0.3/lib/Foreign/GreenCard.hs
greencard-3.0.3/lib/GreenCard.gc
greencard-3.0.3/lib/Makefile
greencard-3.0.3/lib/package.conf.in
greencard-3.0.3/LICENSE
greencard-3.0.3/Makefile
greencard-3.0.3/README
greencard-3.0.3/Setup.hs
greencard-3.0.3/src/
greencard-3.0.3/src/Casm.lhs
greencard-3.0.3/src/Decl.lhs
greencard-3.0.3/src/DIS.lhs
greencard-3.0.3/src/ErrMonad.lhs
greencard-3.0.3/src/ErrorHook.c
greencard-3.0.3/src/FillIn.lhs
greencard-3.0.3/src/FillInMonad.lhs
greencard-3.0.3/src/GCToken.lhs
greencard-3.0.3/src/greencard.ghc.in
greencard-3.0.3/src/greencard.hugs.in
greencard-3.0.3/src/GreenCard.lhs
greencard-3.0.3/src/Lex.lhs
greencard-3.0.3/src/LexM.lhs
greencard-3.0.3/src/ListUtils.lhs
greencard-3.0.3/src/Makefile
greencard-3.0.3/src/MarshallMonad.lhs
greencard-3.0.3/src/Name.lhs
greencard-3.0.3/src/NameSupply.lhs
greencard-3.0.3/src/Package.lhs
greencard-3.0.3/src/Package.lhs.in
greencard-3.0.3/src/Parse.ly
greencard-3.0.3/src/PrettyUtils.lhs
greencard-3.0.3/src/Proc.lhs
greencard-3.0.3/src/Process.lhs
greencard-3.0.3/src/Target.lhs
greencard-3.0.3/src/Type.lhs
5 (0) 19:27:22 m...@yoyo:/tmp2 $ cd greencard-3.0.3
6 (0) 19:27:24 m...@yoyo:/tmp2/greencard-3.0.3 $ make prefix=/tmp2/
make[1]: Entering directory `/hime/tmp2/greencard-3.0.3/src'
happy  Parse.ly
unused terminals: 1
rm -f .depend
touch .depend
ghc -M -optdep-f -optdep.depend -optdep-xFiniteMap -optdep-xPretty -recomp -O 
-fglasgow-exts Casm.lhs DIS.lhs Decl.lhs ErrMonad.lhs FillIn.lhs 
FillInMonad.lhs GCToken.lhs GreenCard.lhs Lex.lhs LexM.lhs ListUtils.lhs 
MarshallMonad.lhs Name.lhs NameSupply.lhs Package.lhs PrettyUtils.lhs Proc.lhs 
Process.lhs Target.lhs Type.lhs Parse.hs
make[1]: Leaving directory `/hime/tmp2/greencard-3.0.3/src'
make[1]: Entering directory `/hime/tmp2/greencard-3.0.3/src'
ghc -recomp -O -fglasgow-exts -c Target.lhs -o Target.o
ghc -recomp -O -fglasgow-exts -c PrettyUtils.lhs -o PrettyUtils.o
ghc -recomp -O -fglasgow-exts -c Casm.lhs -o Casm.o

Casm.lhs:544:1:
Warning: Pattern match(es) are overlapped
 In a case alternative: _ - ...

Casm.lhs:577:1:
Warning: Pattern match(es) are overlapped
 In a case alternative: _ - ...

Casm.lhs:616:4:
Warning: Pattern match(es) are overlapped
 In a case alternative: _ - ...

Casm.lhs:631:5:
Warning: Pattern match(es) are overlapped
 In a case alternative: _ - ...
ghc -recomp -O -fglasgow-exts -c ListUtils.lhs -o ListUtils.o
ghc -recomp -O -fglasgow-exts -c ErrMonad.lhs -o ErrMonad.o
ghc -recomp -O -fglasgow-exts -c Name.lhs -o Name.o
ghc -recomp -O -fglasgow-exts -c DIS.lhs -o DIS.o
ghc -recomp -O -fglasgow-exts -c Type.lhs -o Type.o
ghc -recomp -O -fglasgow-exts -c Decl.lhs -o Decl.o
ghc -recomp -O -fglasgow-exts -c FillInMonad.lhs -o FillInMonad.o
ghc -recomp -O -fglasgow-exts -c NameSupply.lhs -o NameSupply.o
ghc -recomp -O -fglasgow-exts -c FillIn.lhs -o FillIn.o
ghc -recomp -O -fglasgow-exts -c GCToken.lhs -o GCToken.o
ghc -recomp -O -fglasgow-exts -c MarshallMonad.lhs -o MarshallMonad.o
ghc -recomp -O -fglasgow-exts -c Proc.lhs -o Proc.o
ghc -recomp -O -fglasgow-exts -c LexM.lhs -o LexM.o
ghc -recomp -O -fglasgow-exts -c Lex.lhs -o Lex.o
ghc -recomp -O -fglasgow-exts   -Onot  -c Parse.hs -o Parse.o

Parse.hs:1733:1:
Warning: Pattern match(es) are overlapped
 In a case 

Solved (Was: [Haskell-cafe] cannot build greencard)

2009-09-02 Thread mf-hcafe-15c311f0c


Yes, it works:

$ greencard -V
greencard, version 3.00

(Daniel: You were right; I made the mistake of following the
instructions in the README :).  Now I've finally switched to Cabal,
and that did the trick.  Bulat: Yes, I am aware of all the other
projects, but greencard seems to be a front-end to FFI, and it looks
alive enough to me right now, right?)

(Btw the report-bugs-to e-mail doesn't work.)

(Btw2:

diff -r cabal-install-0.6.2/bootstrap.sh cabal-install-0.6.2-/bootstrap.sh
166c166
 dep_pkg parsec 2\.
---
 dep_pkg parsec 3\.

shouldn't be a problem, right?)


Thanks everybody,
Cheers,
Matthias



On Wed, Sep 02, 2009 at 11:41:34PM +0200, Daniel Fischer wrote:
 To: haskell-cafe@haskell.org
 Cc: Dan Weston weston...@imageworks.com,
   mf-hcafe-15c311...@etc-network.de mf-hcafe-15c311...@etc-network.de
 From: Daniel Fischer daniel.is.fisc...@web.de
 Date: Wed, 2 Sep 2009 23:41:34 +0200
 Subject: Re: [Haskell-cafe] cannot build greencard
 
 Am Mittwoch 02 September 2009 23:23:47 schrieb Dan Weston:
  Yet strangely, the last upload was Sun Apr 19 21:42:04 UTC 2009 and
  hackage claims it builds without failure with ghc-6.10.
 
  And in fact it builds just fine for me, so maybe it is worth finding out
  why it doesn't build for you. Are you using ghc-6.10.4 and the latest
  version of cabal?
 
 He used make, not cabal.
 My guess is that the makefiles haven't been updated because we now have Cabal 
 and cabal.
 Formerly, Text.PrettyPrint.HughesPJ was in base, now it's in pretty, since 
 --make is none 
 of the HC_OPTIONS in the makefiles, ghc can't find HughesPJ, thus the linker 
 errors.
 
  
  ** ACCEPT: CRM114 PASS osb unique microgroom Matcher ** 
 CLASSIFY succeeds; success probability: 1.  pR: 11.1886
 Best match to file #0 (nonspam.css) prob: 1.  pR: 11.1886  
 Total features in input file: 2456
 #0 (nonspam.css): features: 758386, hits: 2553116, prob: 1.00e+00, pR:  11.19 
 #1 (spam.css): features: 1686574, hits: 2754260, prob: 6.48e-12, pR: -11.19 
  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe