Re: [Haskell-cafe] Best practice for embedding files in a GHC-compiled tool?

2008-02-07 Thread Dave Bayer

On Feb 7, 2008, at 12:27 AM, [EMAIL PROTECTED] wrote:

Are you assuming that the various users have GHC/Hugs installed? You  
know about scripting through the 'runhaskell' binary, right?



I do, and I've used this. I don't want to do that here.

Let me say this again: I am making no assumptions whatsoever about  
various users, other than platform. Haskell is not a niche language,  
with the right compile options, it CAN be used in this way.


Here's the extreme case: When one is installing Mac OS X, one has  
access to a command line via a terminal application, but the operating  
system is otherwise very stripped down. Nevertheless, if one  
customizes an install DVD by adding a single command-line tool, one  
can execute that tool in this environment.


I'd rather use Haskell than C for such applications.

With C, we can introduce one file to an alien environment, and it will  
run. I've linked GHC Haskell programs that can be used in this way.  
Such programs can be used by anyone on a given platform. Assuming that  
GHC/Hugs is installed divides the potential audience by a large factor.


Under this extreme hypothesis, how do I embed a compressed tar file  
into a single file command line tool written in Haskell and compiled  
by GHC?


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


[Haskell-cafe] Best practice for embedding files in a GHC-compiled tool?

2008-02-06 Thread Dave Bayer

What is the best way to embed an arbitrary file in a Haskell program?

I would like to use GHC to compile command-line tools to be used with  
OS X. I want the tool to be a single file, not a package or a  
directory, that makes no assumptions about what else is present. For  
example, it should be able to run as part of an OS X install disk.


I want this tool to be self reproducing in the sense that one of its  
options causes it to output its own documentation and source code. I  
want this data to be stored as a compressed file within the tool  
binary itself.


The distribution model I'm imagining here is where one writes a  
program anonymously, that isn't hosted anywhere but is passed from  
user to user because it is useful, and eventually reaches another user  
who wants to modify the code. Assume that intermediate users will care  
less about this, and will try to delete anything that they can. That  
rules out storing the data in a separate file. Think of the M.I.T.  
game Core Wars from the dawn of the computer age. I'm looking for a  
strategy here that will be evolutionarily successful in a fairly  
hostile environment.


In other words, I want to be able to write in Haskell, without losing  
the automatic distribution of source code enjoyed by interpreted  
languages. No one deletes the source code for a Perl script, because  
by doing so they're killing the program.


There must be some library I'm overlooking that would make this very  
easy. All I can think of is to use Template Haskell to read a  
compressed tar file into a Haskell variable. Is that what one does, or  
is there a better way?


Thanks in advance,
Dave

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


[Haskell-cafe] GHC from source makes a great hardware test

2007-08-25 Thread Dave Bayer

I recently did the classic push a shopping cart down the aisle at
Fry's to build a Core 2 Quad computer, with Linux swap and a soft
raid array spread across three 750 GB sata hard disks. I had some
potential first build issues, notably a mishap with the lawn of
copper grass that passes for a 775 cpu socket, followed by an hour of
brain-surgery with a magnifying glass and a tiny screwdriver. I was
very curious to test the stability of this system when it booted up
after all; the best hardware test I could think of was multiple
processes building GHC from source, with each iteration using the
previous GHC binary as the compiler for the new build.

Four iterating GHC builds in parallel is enough to peg all four cores
at 100% indefinitely, with considerable disk activity to the soft raid
array. The most I had going at once was 30 GHC builds; the system
remained responsive enough for me to gracefully change my mind in the
morning.

Building multiple copies of GHC generates a lot of heat; going full
tilt, the computer was drawing 220 watts at the wall. I don't use air
conditioning for my summer office, so I ended up taping a small
bathroom exhaust fan and dimmer switch into the back of a cardboard
box, to collect the hot air from the back of the computer and send it
out the window through a dryer hose. This kept the cores at 40 C (the
enclosure itself has all possible fans) and my office cooler. A
previous passive dryer hose arrangement kept the computer at 50 C,
which is cooler than my MacBook cpu at full tilt, but I like to build
things. Cardboard is an awesome quick prototyping material.

Someone else in the same boat might save some time by modifying my
Bash script. I ran hundreds of GHC builds without a mishap, and
concluded that my system is stable.

 #!/bin/bash

 # ghc-test.sh

 # Bash script to iteratively build ghc from source
 # http://www.haskell.org/ghc

 # usage:
 #   ghc-test iters [ghc]

 # Bash scripting reference: Advanced Bash-Scripting Guide
 # http://tldp.org/LDP/abs/html/index.html

 # Customize these parameters to local installation:

 sourcedir=/home/me/ghc-6.6.1
 src1=${sourcedir}/ghc-6.6.1-src.tar.bz2
 src2=${sourcedir}/ghc-6.6.1-src-extralibs.tar.bz2

 testdir=/media/raid/ghc-test
 log=${testdir}/log.txt
 ghcdir=ghc-6.6.1
 binarypath=driver/ghc/ghc


 # determine build directory
 time=$(date +'%Y%m%d-%H%M%S')
 builddir=${testdir}/${time}


 # determine number of iterations
 if [[ -z $1 ]]
 then
 iters=2
 else
 iters=$1
 fi


 # choose ghc binary to use
 if [[ -n $2  -f $2  -x $2 ]]
 then
 ghc=$2
 else
 ghc=$(which ghc)
 fi


 # check ghc binary for pulse
 fib=`${ghc} -e 'let x = 0 : 1 : zipWith (+) x (tail x) in x !! 99'`
 if [[ ${fib} != 218922995834555169026 ]]
 then
 echo ** bad ** ${ghc} ${iters} ${time}  ${log}
 ghc=$(which ghc)
 else
 echo ok${ghc} ${iters} ${time}  ${log}
 fi


 # do an iteration if $iters  0
 let iters=iters-1
 if [[ ${iters} -gt 0 ]]
 then

 # build new copy of ghc from source
 mkdir -p ${builddir}
 cd ${builddir}
 tar -jxf ${src1}
 tar -jxf ${src2}
 cd ${ghcdir}
 ./configure --with-ghc=${ghc}
 make

 # delete previous build directory, now that we're done with $ghc
 if [[ -n $3  -d $3 ]]
 then
 rm -rf $3
 fi

 # iterate
 newghc=${builddir}/${ghcdir}/${binarypath}
 ${sourcedir}/ghc-test.sh ${iters} ${newghc} ${builddir}

 else

 # delete previous build directory
 if [[ -n $3  -d $3 ]]
 then
 rm -rf $3
 fi

 fi

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


[Haskell-cafe] Re: When is waitForProcess not necessary?

2007-08-03 Thread Dave Bayer
Bryan O'Sullivan bos at serpentine.com writes:
 
 Pardon me while I veer off-topic, but you could also use Pandoc to do 
 this.  No forking required.
 http://sophos.berkeley.edu/macfarlane/pandoc/

What I'm doing is neither Haskell nor Markdown specific; I allow any HTML
markup filter that plays nice with the direct HTML I also write (a
restriction I could easily drop), and I cooperate with language-specific
library doc generators such as Haddock.

For all the fuss one reads about Haskell-not-as-fast-as-C, it's amusing how
sluggish Markdown.pl is. Someone should write a small BSD'd Haskell version
as example code for programming in Haskell. I may, although I can't see
myself writing anything called SmartyPants.

I admire pandoc and I allow its use as an alternative to Markdown.pl, as
an external command. I don't want to link it into my code because

* It is GPL'd and I'm writing BSD'd code
* It is a library that does not come with GHC.
* It is twice the length of my code so far.

The Hackage/Cabal universe takes the perspective that one is a committed
Haskell user, and one wants the same diversity of tools enjoyed, say, in
the Perl universe. When one uses Haskell to write a tool whose use is
standalone and not Haskell-specific, there's a very good chance that
someone will come along and try to build it for a new platform, installing
and using GHC for the first time in order to do so. The barrier to entry is
easily doubled if one has to also figure out how to obtain libraries that
do not come automatically with GHC. Plenty of us have the moxie to install
a package like GHC for a single use, because we've heard that hackers can
do such things easily, but we don't really want to join each treehouse.

I've installed versions of, say, Perl, Python, Ruby, even if there was a
possibly lame installation already present. Still, their package systems
generally left me fuming. I know my audience; we mathematicians can be
smart and incredibly stupid at the same time.

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


[Haskell-cafe] Re: When is waitForProcess not necessary?

2007-08-03 Thread Dave Bayer
So I stared at the documentation in Control-Concurrent, learned about
finally and MVar variables, and crossed the genes from the suggestions here
to come up with

runCommand ::  String - String - IO (String,Bool)
runCommand cmd input = do
 (inp,out,err,pid) - runInteractiveCommand cmd
 let get h = do
mvar - newEmptyMVar
let put xs = seq (length xs) (putMVar mvar xs)
forkIO $ finally (hGetContents h = put) (put [])
takeMVar mvar
 if null input then return () else hPutStr inp input
 output - get out
 errmsg - get err
 exit   - waitForProcess pid
 case exit of
  ExitSuccess - return (output,True)
  ExitFailure _ - do
hPutStrLn stderr errmsg
return (errmsg,False)

which seems to work well; I haven't beat on it. I like the return type for
my needs, e.g. I can write

(out,ok) - runCommand mark doc
if ok then write out src
 else hPutStr stderr out 

So why don't the MVar examples in this thread bracket somehow, e.g. with
finally as Control-Concurrent suggests:

Note that we use finally from the Control.Exception module to make
sure that the MVar is written to even if the thread dies or is killed
for some reason.

It seems to me that this could happen, with waitForProcess doing fine, yet
the MVar never getting written. (I haven't written a test example to
exercise this.)


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


[Haskell-cafe] Re: Definition of the Haskell standard library

2007-07-30 Thread Dave Bayer
Chris Smith cdsmith at twu.net writes:

 Can someone clarify what's going on with the standard library in 
 Haskell?
...
 sites for the thousandth time before realizing that so-and-so's GUI 
 library hasn't actually been touched since they finished their class 

Short answer: Our system is very democratic.

Long answer:

You remind me of the usual academic debate, what to do about students using
the web to do research? There's a lot of uncertain information out there,
the right answer is to teach discrimination skills.

Put differently, take the most famous problem in computer science, P vs
NP. If a genie in a bottle is going to lie to you a couple of times before
telling you a truth you can easily check, you're still better off.

In, say, Perl, it's all about the libraries. One connects lots of pieces
one doesn't understand with short bits of line noise, and gets serious
real-world work done.

That's one pole in a range of attitudes. I may be near the other pole; in a
hurry I'll use libraries included with GHC without looking at the source
code. I view anything else in hackage as a truly awesome repository of
sample code. It's on me to make sure that it works, or that I should be
using it at all, rather than doing something else.

My pet example is a PDF library. No language should have its own PDF
library, when Postscript is so easy to write, and Ghostscript is a
cross-platform conversion tool maintained by thousands of our best and
brightest.

So our Haskell desire to have lots of libraries is another version of How
big should a language be? The Common Lisp specification has an appendix
bigger than the Scheme specification in its entirety.

I've gone through several cycles in the last decade of getting rid of half
my possessions; I get more than twice the utility out of what's left, in
part because I understand and I can find what's left. Programming languages
are the same story; I prefer lean.

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


[Haskell-cafe] Re: Avoiding boilerplate retrieving GetOpt cmd line args

2007-07-27 Thread Dave Bayer
Neil Mitchell ndmitchell at gmail.com writes:

 then lookup, instead of just  as the else clause.

Thanks, all. After digesting what was on this thread as I woke up this
morning, I ended up writing something rather close to this.

I have a reusable wrapper around System.Console.GetOpt that adds

 type Opt a = (a,String)
 
 noArg :: a - ArgDescr (Opt a)
 noArg x = NoArg (x,)
 
 reqArg :: a - String - ArgDescr (Opt a)
 reqArg x s = ReqArg f s
 where f y = (x,y)
 
 optArg :: a - String - ArgDescr (Opt a)
 optArg x s = OptArg f s
 where f (Just y) = (x,y)
   f Nothing  = (x,)
 
 isOption :: Eq a = a - [Opt a] - Bool
 isOption opt assoc =  case lookup opt assoc of
 Nothing - False
 Just _  - True
 
 getOption :: Eq a = a - [Opt a] - String
 getOption opt assoc = case lookup opt assoc of
 Nothing - 
 Just s  - s

Then in a project-specific module I write

 data Flag
 = Filter
 | DateFormat
 | DocStart
 | DocEnd
 | ForceStyle
 | Help
 deriving (Eq)
 
 defaults :: [Opt Flag]
 defaults =
 [ (Filter, Markdown.pl)
 , (DateFormat, %B %e, %Y)
 , (DocStart,   ^\\s*{-\\s*$)
 , (DocEnd, ^\\s*-}\\s*$)
 ]
 
 flags :: [OptDescr (Opt Flag)]
 flags =
 [ Option ['s'] [style]  (noArg ForceStyle)
 Overwrite existing style.css
 , Option ['m'] [markup] (reqArg Filter path)
 Path to Markdown-style markup filter
 , Option ['d'] [date]   (reqArg DateFormat format)
 Unix-style modification date format
 , Option ['a'] [start]  (reqArg DocStart string)
 Documentation start string
 , Option ['b'] [end](reqArg DocEnd string)
 Documentation end string
 , Option ['h'] [help]   (noArg Help)
 Print this help message
 ]

which looks almost like the sample code I started with. Reading quickly,
one might miss the case change from `NoArg` to `noArg`, etc.

This is simple, and it works, with less option-specific boilerplate. One
could imagine generating `flags` automatically from an extension of
`defaults`, but I'm content to move on.

The relevant code is at

http://www.math.columbia.edu/~bayer/Haskell/Annote/GetOpt.html
http://www.math.columbia.edu/~bayer/Haskell/Annote/Flags.html
http://www.math.columbia.edu/~bayer/Haskell/Annote/Main.html


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


[Haskell-cafe] Avoiding boilerplate retrieving GetOpt cmd line args

2007-07-26 Thread Dave Bayer
Ok, I'm writing a command line tool, using System.Console.GetOpt to  
handle command line arguments. My Flags structure so far is



data Flag
= Filter String
| DateFormat String
| DocStart String
| DocEnd String

...

and I want to write accessor functions that return the strings if  
specified, otherwise returning a default. The best I've been able to  
do is this:



getFilter = getString f Markdown.pl
where f (Filter s) = Just s
  f _ = Nothing

getDateFormat = getString f %B %e, %Y
where f (DateFormat s) = Just s
  f _ = Nothing

getDocStart = getString f ^{-$
where f (DocStart s) = Just s
  f _ = Nothing

getDocEnd = getString f ^-}$
where f (DocEnd s) = Just s
  f _ = Nothing


using a generic accessor function `getString`.

There are eight (and growing) needless lines here, where what I  
really want to do is to pass the constructors `Filter`, `DateFormat`,  
`DocStart`, or `DocEnd` to the function `getString`. ghci types each  
of these as `String - Flag`, so one at least knows how to type such  
a `getString`, but using a constructor-passed-as-an-argument in a  
pattern match is of course a Parse error in pattern. (I expected as  
much, but I had to try... `String - Flag` is not enough information  
to make it clear we're passing a constructor, rather than some hairy  
arbitrary function, so such a pattern match would be undecidable in  
general.)


So what's the right idiom for avoiding this boilerplate?

Thanks,
Dave

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


[Haskell-cafe] Re: Compile-time here document facility

2007-07-25 Thread Dave Bayer
Donald Bruce Stewart dons at cse.unsw.edu.au writes:

 bayer:
  I couldn't find a compile-time here document facility, so I wrote one  
  using Template Haskell:
 
 Very nice! You should wrap it in a little .cabal file, and upload it to
 hackage.haskell.org, so we don't forget about it.
 
 Details on cabalising and uploading here:
 
 http://haskell.org/haskellwiki/How_to_write_a_Haskell_program
 http://cgi.cse.unsw.edu.au/~dons/blog/2006/12/11

I was waiting for the other shoe to drop, as usual. I tweaked the code a
bit, and I'm getting ready to contribute it to Hackage, as I find it
useful. The current source can be found at

http://www.math.columbia.edu/~bayer/Haskell/Annote/HereDocs.html

Basically, it bothered me that I was using assert to figure out the file
name (an idea that others have also had) because asserts disappear under
optimization. I looked again at Control.Exception, and I realized that I
would be better off catching a pattern-matching exception:

$(hereDocs $ let [e] = [] in e)

(Can anyone come up with a shorter pattern match failure, that can be used
as a value here?)

Of course, anything like this is like gas fireplace logs, pointlessly
recreating the past. There is little wrong with simply hard-coding the file
name; GHC has this nice way of letting me know when code like this gets out
of sync:

$(hereDocs Strings.hs)

So here is my question:

 The source should live under a directory path that fits into the existing
 module layout guide.
 http://www.haskell.org/~simonmar/lib-hierarchy.html

A here document is a kind of data, but it is really a language extension,
and one that depends on a GHC extension, Template Haskell. I'd go for

Data.HereDocs

but that doesn't seem quite right. The newbie in me doesn't want to park my
car in your living room, so to speak. What's the right place for this?

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


[Haskell-cafe] Re: Code and Perf. Data for Prime Finders (was: Genuine Eratosthenes sieve)

2007-07-23 Thread Dave Bayer

As an exercise, trying to understand the beautiful paper

Stream Fusion
From Lists to Streams to Nothing at All
Duncan Coutts, Roman Leshchinskiy and Don Stewart
http://www.cse.unsw.edu.au/~dons/papers/CLS07.html
http://www.cse.unsw.edu.au/~dons/streams.html

I recoded my prime sieve using a pared down version of their Stream  
datatype; this is the simplest version I could write that  achieves a  
significant speedup.


My reaction to their paper was, if streams are better internally than  
lists, why not code directly in streams? Lists enjoy a serious  
notational advantage in Haskell, but one could imagine a language  
where the list notation was reserved for stream semantics.


My sieve was spending half its time in merge, so I made only the  
changes necessary to convert merge to use streams. My streams are  
infinite, and merge can be written to not use Skip, so Step goes away.


Even though nextx and nexty only have one case now, using case  
statements is significantly faster than using let or where clauses.  
I'm imagining that I read about this somewhere, but if I did, it  
didn't sink in until I was tuning this code. I don't know if this is  
related to fusion optimization, or a general effect.


The timings are


[Integer] -O2  1*10^6   2*10^6   3*10^6   4*10^6   5*10^6
-
ONeillPrimes |  3.338 |  7.320 | 11.911 | 18.225 | 21.785
StreamPrimes |  3.867 |  8.405 | 13.656 | 21.542 | 37.640
BayerPrimes  |  3.960 |  8.940 | 18.528 | 33.221 | 38.568


Here is the code:


{-# OPTIONS_GHC -fglasgow-exts #-}

module StreamPrimes (primes) where

-- stream code

data Stream a = forall s. Stream (s - (a,s)) s
data AStream a = A a (AStream a) | B (Stream a)

stream :: [a] - Stream a
stream xs = Stream next xs
  where
next [] = undefined
next (x:xt) = (x,xt)

astream :: [a] - AStream a
astream [] = undefined
astream (x:xt) = A x $ B $ stream xt

merge :: Ord a = Stream a - Stream a - Stream a
merge (Stream nextx vs) (Stream nexty ws) =
Stream next (vt,ws,Left v)
where
(v,vt) = nextx vs
next (xs,ys,Left x) =
case nexty ys of
(y,yt) -
if   x  y
then (x,(xs,yt,Right y))
else (y,(xs,yt,Left x))
next (xs,ys,Right y) =
case nextx xs of
(x,xt) -
if   x  y
then (x,(xt,ys,Right y))
else (y,(xt,ys,Left x))

mergeA :: Ord a = AStream a - AStream a - AStream a
mergeA (A x xt) ys = A x (mergeA xt ys)
mergeA (B xs)   ys = mergeB xs ys

mergeB :: Ord a = Stream a - AStream a - AStream a
mergeB s@(Stream next xs) ys@(A y yt) =
case next xs of
(x,xt) -
if x  y
then A x (mergeB (Stream next xt) ys)
else A y (mergeB s yt)
mergeB xs (B ys) = B $ merge xs ys

-- Code for venturi :: Ord a = [[a]] - [a]

root :: Ord a = AStream a - [AStream a] - [a]
root (A x xt) yss= x : (root xt yss)
root (B xs) (ys:yst) = root (mergeB xs ys) yst
root _ _ = undefined

pair :: Ord a = [AStream a] - [AStream a]
pair (x:y:xt) = mergeA x y : (pair xt)
pair _ = undefined

group :: Ord a = [AStream a] - [AStream a]
group (x:xt) = x : (group $ pair xt)
group _ = undefined

venturi :: Ord a = [[a]] - [a]
venturi (x:xt) = root (astream x) $ group $ map astream xt
venturi _ = undefined

-- Code for primes :: Integral a = [a]

diff  :: Ord a = [a] - [a] - [a]
diff xs@(x:xt) ys@(y:yt) = case compare x y of
LT - x : (diff  xt ys)
EQ - (diff  xt yt)
GT - (diff  xs yt)
diff _ _ = undefined

trim :: Integral a = a - [a] - [a]
trim p = let f m x = mod x m /= 0 in filter (f p)

seed :: Integral a = [a]
seed = [2,3,5,7,11,13,17]

wheel :: Integral a = [a]
wheel = drop 1 [ m*j + k | j - [0..], k - ws ]
where m  = foldr1 (*) seed
  ws = foldr trim [1..m] seed

multiples :: Integral a = [a] - [[a]]
multiples ws = map fst $ tail $ iterate g ([], ws)
where g (_,ps@(p:pt)) = ([ m*p | m - ps ], trim p pt)
  g _ = undefined

primes :: Integral a = [a]
primes = seed ++ (diff wheel $ venturi $ multiples wheel)



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


[Haskell-cafe] Re: Frustrating experience of a wannabe contributor

2007-07-23 Thread Dave Bayer
Simon Michael simon at joyful.com writes:

 
 Hi Andreas - very good problem report, thanks.
 
 I have just cleaned up the archive links at 
 http://www.haskell.org/haskellwiki/Mailing_lists a bit. I added the 
 ever-excellent gmane and an overview of all archives.

Ok, this list was crushing my OS X Mail program (not the
coldest beer in the fridge) so I went to a hybrid approach
of reading on gmane, and using NetNewsWire to track the
news feed from gmane.

As a result, I don't have original mail messages to reply
to. I nevertheless want to use my Mail program to
originate posts, in order to cc: interested parties
directly as appears to be the custom, and in hopes that at
least some recipients won't have xs@(x,xt) in Haskell
source code rewritten as xs at (x,xt).

When I send a message Re: thread it appears to break the
thread, showing up as a singleton in gmane's thread list.

It appears that I am caught between a rock and a hard
place.

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


[Haskell-cafe] Re: Code and Perf. Data for Prime Finders (was: Genuine Eratosthenes sieve)

2007-07-23 Thread Dave Bayer
It appears that at least on gmane, my posts to this thread ended up as
singletons, breaking the thread. Here are the posts:

http://article.gmane.org/gmane.comp.lang.haskell.cafe/26426
http://article.gmane.org/gmane.comp.lang.haskell.cafe/26466


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


[Haskell-cafe] Re: Code and Perf. Data for Prime Finders (was: Genuine Eratosthenes sieve)

2007-07-22 Thread Dave Bayer
Here is another prime sieve. It is about half the length of the  
fastest contributed code (ONeillPrimes) and nearly as fast until it  
blows up on garbage collection:



% cat ONeillPrimes.hs | grep -v ^-- | wc
 18511056306
% cat BayerPrimes.hs  | grep -v ^-- | wc
  85 5662418

[Integer] -O   1*10^6   2*10^6   3*10^6   4*10^6   5*10^6
-
ONeillPrimes |  3.555 |  7.798 | 12.622 | 18.927 | 23.529
BayerPrimes  |  3.999 |  8.895 | 18.003 | 22.977 | 38.053


I wrote this as an experiment in coding data structures in Haskell's  
lazy evaluation model, rather than as explicit data. The majority of  
the work done by this code is done by merge; the multiples of each  
prime percolate up through a tournament consisting of a balanced tree  
of suspended merge function calls. In order to create an infinite  
lazy balanced tree of lists, the datatype



data List a = A a (List a) | B [a]


is used as scaffolding. One thinks of the root of the infinite tree  
as starting at the leftmost child, and crawling up the left spine as  
necessary.


What I'm calling a venturi


venturi :: Ord a = [[a]] - [a]


merges an infinite list of infinite lists into one list, under the  
assumption that each list, and the heads of the lists, are in  
increasing order. This could be a generally useful function. If one  
can think of a better way to write venturi, swapping in your code  
would in particular yield a faster prime sieve.


I found that a tertiary merge tree was faster than a binary merge  
tree, because this leads to fewer suspensions. One can speed this  
code up a bit by interleaving strict and lazy calls, but I prefer to  
leave the code short and readable.


It is bizarre that


trim p = let f m x = mod x m /= 0 in filter (f p)


lurks in the prime sieve code, but it is only used with primes of  
size up to the square root of the largest output prime. I tried more  
thoughtful alternatives, and they all slowed down the sieve.  
Sometimes dumb is beautiful.


Thanks to apfelmus for various helpful remarks that lead me to think  
of this approach.


Here is the code:


module BayerPrimes (venturi,primes) where

-- Code for venturi :: Ord a = [[a]] - [a]

merge :: Ord a = [a] - [a] - [a] - [a]
merge xs@(x:xt) ys@(y:yt) zs@(z:zt)
| x = y = if x = z
then x : (merge xt ys zs)
else z : (merge xs ys zt)
| otherwise = if y = z
then y : (merge xs yt zs)
else z : (merge xs ys zt)
merge _ _ _ = undefined

data List a = A a (List a) | B [a]

mergeA :: Ord a = List a - List a - List a - List a
mergeA (A x xt) ys zs = A x (mergeA xt ys zs)
mergeA (B xs)   ys zs = mergeB xs ys zs

mergeB :: Ord a = [a] - List a - List a - List a
mergeB xs@(x:xt) ys@(A y yt) zs = case compare x y of
LT - A x (mergeB xt ys zs)
EQ - A x (mergeB xt yt zs)
GT - A y (mergeB xs yt zs)
mergeB xs (B ys) zs = mergeC xs ys zs
mergeB _ _ _ = undefined

mergeC :: Ord a = [a] - [a] - List a - List a
mergeC xs@(x:xt) ys@(y:yt) zs@(A z zt)
| x  y = if x  z
then A x (mergeC xt ys zs)
else A z (mergeC xs ys zt)
| otherwise = if y  z
then A y (mergeC xs yt zs)
else A z (mergeC xs ys zt)
mergeC xs ys (B zs) = B $ merge xs ys zs
mergeC _ _ _ = undefined

root :: Ord a = List a - [List a] - [a]
root (A x xt) yss   = x : (root xt yss)
root (B xs) (ys:zs:yst) = root (mergeB xs ys zs) yst
root _ _ = undefined

wrap :: [a] - List a
wrap [] = B []
wrap (x:xt) = A x $ B xt

triple :: Ord a = [List a] - [List a]
triple (x:y:z:xs) = mergeA x y z : (triple xs)
triple _ = undefined

group :: Ord a = [List a] - [List a]
group (x:y:xt) = x : y : (group $ triple xt)
group _ = undefined

venturi :: Ord a = [[a]] - [a]
venturi (x:xt) = root (wrap x) $ group $ map wrap xt
venturi _ = undefined

-- Code for primes :: Integral a = [a]

diff  :: Ord a = [a] - [a] - [a]
diff xs@(x:xt) ys@(y:yt) = case compare x y of
LT - x : (diff  xt ys)
EQ - (diff  xt yt)
GT - (diff  xs yt)
diff _ _ = undefined

trim :: Integral a = a - [a] - [a]
trim p = let f m x = mod x m /= 0 in filter (f p)

seed :: Integral a = [a]
seed = [2,3,5,7,11,13,17]

wheel :: Integral a = [a]
wheel = drop 1 [ m*j + k | j - [0..], k - ws ]
where m  = foldr1 (*) seed
  ws = foldr trim [1..m] seed

multiples :: Integral a = [a] - [[a]]
multiples ws = map fst $ tail $ iterate g ([], ws)
where g (_,ps@(p:pt)) = ([ m*p | m - ps ], trim p pt)
  g _ = undefined

primes :: Integral a = [a]
primes = seed ++ (diff wheel $ venturi $ multiples wheel)


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


[Haskell-cafe] Re: Hints for Euler Problem 11

2007-07-20 Thread Dave Bayer
Ronald Guida ronguida at mindspring.com writes:

 I started looking at the Euler problems [1].  I had no trouble with
 problems 1 through 10, but I'm stuck on problem 11.  I am aware that
 the solutions are available ([2]), but I would rather not look just
 yet.

I am the author of that solution

http://www.haskell.org/haskellwiki/Euler_problems/11_to_20

My solution has a word count of 191 words, which might amuse you considering
that there are 400 entries to the table.

Hint: zipWith4 is your friend; see Data.List. Feed it four lists of different
lengths, and it stops gracefully when any list runs out. So one can use

skew (w,x,y,z) = (w, drop 1 x, drop 2 y, drop 3 z)

to stagger four lists before multiplying corresponding elements.

I was using the Euler problems to learn Haskell, as you're doing, so I don't
know if my solution is the most readable one. I built up a vocabulary of short
functions to compose.

I remember finding it odd at the time that I had to use tuples to handle
multiple return values. C annoyed me for being mostly peanut shells and few
peanuts: one seems to spend all of one's time tossing arguments back and forth
onto the stack for nested function calls, when it seemed that the real work
could be done in place with less effort. Sure, optimizing compilers do exactly
that, with registers, but then why was I explicitly worrying about passing
around all of these arguments, in order to code in C?

Haskell is much more concise, but the tupling and untupling in my code seems a
distraction, even looking back at it now.

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


[Haskell-cafe] Re: no-coding functional data structures via lazyness

2007-07-16 Thread Dave Bayer
apfelmus apfelmus at quantentunnel.de writes:

 While your observation that merge may create an implicit heap is true,
 it doesn't happen in your code :) When unfolding the foldr1, we get
 something like
 
   2:.. `merge'` (3:.. `merge'` (5:.. `merge1` (...)))
 
 i.e. just a linear chain of merges. Retrieving the least element is
 linear time in the worst case. This shape will not change with
 subsequent reductions of  merge. In other words, it's the responsibility
 of  fold  to build a heap. Mergesort shows how a fold can build a heap:
 
   http://thread.gmane.org/gmane.comp.lang.haskell.general/15007
 
 For  primes , the heap shape has to be chosen carefully in order to
 ensure termination. It's the same problem that forces you to use  foldr1
 merge'  instead of  foldr1 merge .
 
 There's also a long thread about prime sieves
 
   http://thread.gmane.org/gmane.comp.lang.haskell.cafe/19699

Indeed. Your answer sent my head spinning, giving me something to think about
on a flight AMS to SFO. Thanks!

Here is a prime sieve that can hang within a factor of two of the fastest
code in that thread, until it blows up on garbage collection:

-

diff  :: Ord a = [a] - [a] - [a]
diff xs@(x:xt) ys@(y:yt) = case compare x y of
LT - x : (diff  xt ys)
EQ - (diff  xt yt)
GT - (diff  xs yt)
diff _ _ = undefined

union :: Ord a = [a] - [a] - [a]
union xs@(x:xt) ys@(y:yt) = case compare x y of
LT - x : (union xt ys)
EQ - x : (union xt yt)
GT - y : (union xs yt)
union _ _ = undefined

twig :: Ord a = [a] - [a] - [a]
twig (x:xt) ys = x : (union xt ys)
twig _ _ = undefined

pair :: Ord a = [[a]] - [[a]]
pair (x:y:xs) = twig x y : (pair xs)
pair _ = undefined

tree :: Ord a = [[a]] - [a]
tree xs  = 
let g (x:xt) = x : (g $ pair xt)
g _ = undefined
in  foldr1 twig $ g xs

seed :: Integral a = [a]
seed = [2,3,5,7,11,13]

wheel :: Integral a = [a]
wheel  = drop 1 [ 30*j+k | j - [0..], k - [1,7,11,13,17,19,23,29] ]

multiples :: Integral a = [a]
multiples = tree ps
where f p n = mod n p /= 0
  g (_,ns) p = ([ n*p | n - ns ], filter (f p) ns)
  ps = map fst $ tail $ scanl g ([], wheel) $ drop 3 primes

primes :: Integral a = [a]
primes = seed ++ (diff (drop 3 wheel) multiples)

-

Here are some timings:

[Integer] -O   10^410^510^610^7
-
ONeillPrimes  |  0m0.023s |  0m0.278s |  0m3.682s | 0m53.920s
  primes  |  0m0.022s |  0m0.341s |  0m5.664s | 8m12.239s

This differs from your code in that it works with infinite lists, so
it can't build a balanced tree; the best it can do is to build a vine
of subtrees that double in size.

My conclusion so far from this and other experiments is that pushing
data structures into the lazy evaluation model does make them run faster,
but at the expense of space, which eventually leads to the code's untimely
demise.

I can imagine a lazy functional language that would support reification
of suspended closures, so one could incrementally balance the suspended
computation above. As far as I can tell, Haskell is not such a language.
I'd love it, however, if someone could surprise me by showing me the
idiom I'm missing here.

I will post a version of this code (I have faster but less readable
versions) to the prime sieve thread. First, I'm waiting for
the other shoe to drop, I still feel like I'm missing something.

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


[Haskell-cafe] Re: Haskell for categorists

2007-07-16 Thread Dave Bayer
Miguel Mitrofanov miguelimo38 at yandex.ru writes:

 There are a lot of tutorials ensuring the reader that, although
 Haskell is based on category theory, you don't have to know CT to use
 Haskell. So, is there ANY Haskell tutorial for those who do know CT?

If you know category theory, it's a good bet that you're used to learning new
subjects by reading research papers. You may even subscribe to the old acorn
that it's best to read original sources.

One can't learn Haskell _just_ by reading papers, but it sure helps give
perspective on how Haskell came to be, which in turn helps Haskell make more
sense. Go read the original papers suggesting that category theory might be
helpful in functional programming. Then try to find monads in the classic
category theory textbooks, and stare at the surrounding pages.

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


[Haskell-cafe] Re: Perfect shuffle on std. libs

2007-07-14 Thread Dave Bayer
Felipe Almeida Lessa felipe.lessa at gmail.com writes:

 I wonder why Oleg's perfect shuffle[1] isn't on any standard library?

This is incorrect terminology: A perfect shuffle is one where the cards
interleave in a 1:1:1:1:1... pattern, achieving exactly the same permutation of
the deck each time. For example, a perfect shuffle of 52 cards where the top and
bottom cards stay fixed has order 8: Do one eight times and the deck will return
to its original ordering. Most people are incapable of executing a perfect
shuffle, but various magicians have mastered this as sleight of hand. 

I am one of the authors of

  Dave Bayer, Persi Diaconis
  Trailing the dovetail shuffle to its lair
  Ann. Appl. Probab. 2 (1992), no. 2, 294-313

which found a closed form formula for the probabilities involved in riffle
shuffles, how people shuffle e.g. playing bridge. This work was summarized as
seven shuffles suffice. I once watched my coauthor, Persi, perform a card
trick as part of a talk, where he threw in a shuffle just to amuse himself
before starting the trick. It happened to be a perfect shuffle, or the trick
would have failed. I chortled eight hours later in a solemn moment in a modern
dance concert, it took me this long to realize he had done this.

What Oleg means is that his code achieves a uniform distribution after one pass.



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


[Haskell-cafe] Re: Maintaining the community

2007-07-13 Thread Dave Bayer
Claus Reinke claus.reinke at talk21.com writes:

 will ultimately make its contents easier to find. but if you
 want to avoid answering questions again and again on the
 list, you need to improve the cache of answers.

Bingo. On less technical forums, e.g. FlyerTalk, the do a search equivalent to
RTFM is rampant and people goal-tend without actually doing a test search to
find out if that search might not be coming up for some reason. Others say do a
search but demonstrate an effective keyword combination and the resulting
useful resource.

Here, the Wiki is fantastic but extraordinarily spotty (any healthy wiki will
always have much new growth, but the current gaps are surprising), and newcomers
like myself can and have been contributing to it.

If somehow the surge in Haskell Cafe interest could be harnessed to feed Wiki
content, that would be great. Something like I noticed the Wiki entry for list
comprehensions is just a stub, so I edited it to answer your question. Is the
answer clear? Your beginner perspective is invaluable; how can it be improved?

The only way to establish such a tradition is by example. I'll start giving it a
try.

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


[Haskell-cafe] Re: Maintaining the community

2007-07-13 Thread Dave Bayer
Malcolm Wallace Malcolm.Wallace at cs.york.ac.uk writes:
 Yes, the sheer volume of posts is definitely becoming a problem (for me,
 at least).

As a newcomer I was stunned that this otherwise very sophisticated community was
using an email list rather than a bulletin board. The shear torrent of email was
impacting my mail program performance.

Then I chased somes repies leading to earlier threads, and found bulletin-board
stye access to our list at

http://thread.gmane.org/gmane.comp.lang.haskell.cafe/

I much prefer this access, even if I wish the window spit vertically rather than
horizontally.

A bulletin board has the capabibility to evolve, e.g. into multiple entry 
points.

Are there statistics on who reads which way? Posting stats should be obvious
with a little script, for anyone who still has a hoard of messagess at homne.

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


[Haskell-cafe] Re: Simple newbie question - Int and Integer

2007-07-13 Thread Dave Bayer
Gregory Propf gregorypropf at yahoo.com writes:

 So what the hell is the difference between them?  Int and Integer.
 They aren't synonyms clearly.  What's going on?

http://www.haskell.org/haskellwiki/Learn_Haskell_in_10_minutes

is a good starting point for answering this and similar questions.


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


[Haskell-cafe] Re: [Math] Category theory research programs?

2007-07-13 Thread Dave Bayer
Creighton Hogg wchogg at gmail.com writes:
 
 Hi Haskell, Sorry to contribute to the noise but given that we've been
 talking about categories lately, I was wondering if anyone had any
 opinions on good universities for studying category theory.  I'm
 trying to figure out where to apply for my phd.  I want to either be
 at a place with a strong category theory program or a strong
 differential geometry program.

Do apply to Columbia. Category theory was partly invented here;
Eilenberg's bust looks out over the common room. As for differential
geometry, we've had ringside seats for Perelman's proof of the
Poincare conjecture, with Morgan and Hamilton on the faculty, and one
can't get to the espresso machine without tripping over a differential
geometer. And a few of us speak Haskell.

I learned what category theory I know as part of Algebraic Geometry,
and share the prejudice that category theory is a language one uses,
rather than studying directly. I certainly had to go back to the books
to understand the different uses in Haskell.

Prejudice or not, if you're sharp enough to be a contender, you'll get
a better job studying differential geometry. You can always study
category theory at the same time, but diff geo will pay the rent.

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


[Haskell-cafe] no-coding functional data structures via lazyness

2007-07-09 Thread Dave Bayer
Learning Haskell, the Prelude.ShowS type stood out as odd, exploiting  
the implementation of lazy evaluation to avoid explicitly writing an  
efficient concatenable list data structure. This felt like cheating,  
or at least like using a screwdriver as a crowbar, to be less  
judgmental.


Recently I was playing with prime sieves and various heap data  
structures, while rereading Chris Okasaki's Purely Functional Data  
Structures, and it dawned on me:



merge xs@(x:xt) ys@(y:yt) = case compare x y of
LT - x : (merge xt ys)
EQ - x : (merge xt yt)
GT - y : (merge xs yt)

diff xs@(x:xt) ys@(y:yt) = case compare x y of
LT - x : (diff xt ys)
EQ - diff xt yt
GT - diff xs yt

merge' (x:xt) ys = x : (merge xt ys)

primes = ps ++ (diff ns $ foldr1 merge' $ map f $ tail primes)
where ps  = [2,3,5]
  ns  = [7,9..]
  f p = [ m*p | m - [p,p+2..]]


The code is very fast for its size; I haven't seen Haskell code  
posted on the web that comes close, and it is faster than any of my  
other tries (I posted this code to http://www.haskell.org/haskellwiki/ 
Prime_numbers). Effectively, it steals a heap data structure out of  
thin air by exploiting the implementation of lazy evaluation. It  
would seem that GHC's core data structures are coded closer to the  
machine that anything I can write _in_ Haskell. So much for studying  
how to explicitly write a good heap!


So is there a name for this idiom, no-coding a classic data  
structure through lazy evaluation? Are there other good examples?


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


Re: [Haskell-cafe] no-coding functional data structures via lazyness

2007-07-09 Thread Dave Bayer


On Jul 9, 2007, at 6:52 PM, Donald Bruce Stewart wrote:


bayer:

Learning Haskell, the Prelude.ShowS type stood out as odd, exploiting
the implementation of lazy evaluation to avoid explicitly writing an
efficient concatenable list data structure.



See also
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ 
dlist-0.3


Thanks; I added a link to the dlist package from my discussion of  
this idiom on the Wiki page

http://www.haskell.org/haskellwiki/Prime_numbers

On Jul 9, 2007, at 3:19 PM, Jonathan Cast wrote:

I think we usually call it `exploiting laziness'. . .


My motivation in asking for a name was to be able to find other  
Haskell one-liners adequately replacing chapters of data structure  
books for problems of modest scale, e.g. finding the 5,000,000th  
prime. So far, I know concatenable lists, and heaps.  Is there a Wiki  
page where someone teaches this principle for a dozen other classic  
data structures? Your one-liner made me laugh, but it didn't help  
me in googling, I would have preferred a one-liner teaching me  
another classic data structure, or an explanation of why burrowing  
into the GHC implementation gives such a speed advantage over a  
carefully written explicit data structure.


People in other camps don't really get lazy evaluation, even many  
of our ML neighbors. It would pay to communicate this better to the  
outside world.



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


Re: [Haskell-cafe] A very edgy language (was: A very nontrivial parser)

2007-07-07 Thread Dave Bayer

On Jul 7, 2007, at 4:23 AM, Thomas Conway wrote:


the performance model for haskell programs is at best inscrutable


I punched my first Basic program by hand with a paper clip, in my  
high school library. Even after experiencing an APL interpreter at  
19, it has taken half my life to fully internalize that how long a  
language takes with a machine isn't the issue, what matters is how  
long a language takes with ME. I was beginning to accept that I might  
die before clearing my pipeline of research projects I want to code  
up. Haskell has given me new hope.


Haskell is like ice sailing, where one can reach 100 mph on a 15 mph  
breeze. A few months ago, I watched a colleague write a significant  
code experiment in Haskell in an hour, and I was stunned. Now, I  
routinely write reasonable code experiments in an hour to help learn  
the language, and I'm still a beginner. It pays to time all  
executions, one can sometimes knock a factor of ten out of a given  
algorithm with a modest amount of tweaking. One learns in the process  
how to write faster code next time on the first try. GHC is very  
impressive if one pays a little attention to one's code.


This of course sets up the best answer to this debate: For a hard  
problem, one can express better algorithms in Haskell that would  
simply be too painful to code in other languages, swamping any  
considerations about the speed of Haskell versus C for a given  
algorithm.


This is not where I'm personally at. I want Haskell to work math  
examples for me that would take months to work by hand. With current  
processor speeds, the bottleneck is how quickly I can specify to the  
computer what I want. Haskell is the perfect language for this. For  
this purpose, concise readable code I can understand later beats hell  
out of a better algorithm. My evolution as a Haskell programmer is to  
say things more clearly with less fuss, not to get the machine to go  
faster.


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


Re: [Haskell-cafe] Binary serialization, was Re: Abstraction leak

2007-07-05 Thread Dave Bayer


On Jul 5, 2007, at 8:00 AM, Paul Moore wrote:


It probably depends on your perspective. I've found lots of tasks that
would be a simple library call in Python, but which require me to
write the code myself in Haskell. Examples:

* Calculate the MD5 checksum of a file


How's this, only one line is specific to your problem:


import System.Process
import IO

doShell :: String - IO String
doShell cmd = do
(_,out,_,_) - runInteractiveCommand cmd
hGetContents out

main :: IO ()
main = do
md5 - doShell md5 -q md5.hs
putStrLn md5


It's not like you'll be kicked out of the tree house for leaving the  
Haskell world to get things done. For example, ghostscript and pdf2ps  
are well-supported open source tools for converting PS to PDF, that  
can be called from most languages. What's the deal with everyone  
rewriting PDF handling in their pet language, when it's so much  
easier to generate Postscript? I'd call that Balkanization; if I were  
managing a software group, I'd never let that happen.


The true problem isn't adequate libraries in each language, it's  
interoperability so great open-source tools can get written once and  
then be supported by a cast of thousands.


There are people who claim with a straight face that they migrated to  
OS X primarily to use TextMate


http://www.textmate.com

which is a GUI editor getting Emacs-like buzz, making Emacs seem by  
comparison like your grandfather's razor. It's as much a text-based  
operating system as an editor, and the whole thing is glued together  
with hundreds of snippets of code one can hack, written in every  
scripting language imaginable. Polyglots feel right at home...


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


Re: [Haskell-cafe] Binary serialization, was Re: Abstraction leak

2007-07-05 Thread Dave Bayer

On Jul 5, 2007, at 9:52 AM, Paul Moore wrote:


You're changing the problem from finding a Haskell library (which only
needs to be installed on the development machine at compile time) to
finding a 3rd party utility, which has to be installed at runtime

...

Not a good trade-off.


The intersection of Linux and Mac OS X is a pretty amazing standard   
library, that beats any single scripting language.


I'd forgotten how dismal Windows is, sorry. Still, if you stick to  
non-GPL'd licenses, there's no way to build single file deliverables?  
I'd think someone would have written Unix as a static library, the  
way e.g. many languages can be embedded in apps. Then only you would  
have to maintain the Unix tools you want to use, and you'd be done.  
If no one has, someone who cares about Windows should. Unix rocks.


On Jul 5, 2007, at 9:54 AM, Philip Armstrong wrote:

Presumably you mean http://macromates.com/ ?


Yup. Sorry.

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


Re: [Haskell-cafe] Parsers are monadic?

2007-06-30 Thread Dave Bayer

On Jun 30, 2007, at 6:31 AM, Claus Reinke wrote:

has anyone else had similar experiences with expressive limitations
of monadic programming? things that one might be able to work
around, but that don't feel as natural or simple as they should be?
things that one hasn't been able to express at all (such as Swierstra
 Duponcheel's static analysis of combinator parsers which
inspired Hughes's proposal to use arrows)?


When you pretend you've never heard of monads or arrows, and write  
down the types what do you get?


When I finally overcame my resistance to monads, I only had to change  
names in my code to use the Maybe monad, the functions already had  
the right type. There's an inevitability to monads and arrows, and  
perhaps to what you're thinking, if it's a third species in a lazy  
list we're evaluating of such things.


--

Haskell does suffer from misrepresentation to outsiders. Even already  
familiar with ML and Ocaml, the lazy, pure approach read to me like  
a fetish, and monads seemed a tainted construct for if one absolutely  
must venture into the practical. The only reason I could see to learn  
Haskell was a sense that nevertheless comes through and probably puts  
some people off, that Haskell programmers are in the highest reading  
group. (Lisp programmers imagine that they are; one should learn  
both.) If one must suffer through the drudgery of using  a  
programming language, shouldn't it be a window to enlightenment that  
Aldous Huxley would admire? Haskell delivers, but I avoided monads to  
get the pure experience, when in fact Haskell is all about  
supporting functional idioms like monads.


The references cited in this thread are excellent. They certainly  
gave me more insight into the history of how Haskell evolved: Classes  
coming from Gofer precisely to make monads more elegant to use, and  
do notation a mutant form of monad comprehensions.


I went chasing references but couldn't substantiate this statement on  
page 11 of


1996 Hutton, Meijer - Monadic parser combinators
	http://haskell.readscheme.org/servlets/cite.ss?pattern=hutton- 
parsers1996


	Indeed, the algebraic properties required of the monad operations  
turn out to be precisely

those required for the notation to make sense.


How do I reconcile this with the extension of do notation to support  
arrows?


If monads and arrows are two instances of something akin to group  
theory then the definition of a group is lurking within whatever  
this quote should have said...

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


Re: [Haskell-cafe] advice: instantiating/duplicating modules

2007-06-29 Thread Dave Bayer

On Jun 29, 2007, at 10:07 AM, Nicolas Frisby wrote:


I wrote a combination reader/writer monad (a la the RWS monad in the
mtl) and I find myself wanting to use multiple instances of it in the
same stack of transformers. The functional dependencies prevent this
from working out.


I found myself in a situation implementing two very similar  
algorithms where I had to really puzzle out how to get functional  
dependencies to work, and I ended up writing a class (I abridge):



class (Num b, Real c) = Elem a b c | a - b, a - c where
   qr :: a - b - b - QR c


and then declaring instances like


data Rlist a = Rlist
instance Integral a = Elem (Rlist a) a (Ratio a) where
   qr w x y = Yes (x % y) False


When I wanted this version of qr, I'd call qr Rlist. Rlist is a  
dummy class parameter to get the functional dependencies to work, it  
does nothing besides select a version of my code. I couldn't get the  
functional dependencies to work out any other way, so I accepted this.


Later, I realized that Haskell had named records, and I went back and  
rewrote stuff as follows:



data (Num b, Real c) = Elem b c = Elem {
qr :: b - b - Rem c }

rlist :: Integral a = Elem a (Ratio a)
rlist = Elem {
qr = (\x y - Just (x % y, False)) }


Now all I had to do was change the case from qr Rlist to qr rlist  
and the rest of my code worked exactly as before. (I love how often  
this sort of thing happens in Haskell.) I went from thinking that  
passing around a bunch of functions was kludgey, to thinking that a  
beginner like me using multi-parameter type classes unnecessarily was  
obfuscation. In any case, it didn't matter what I thought, the code  
either way was virtually identical.


I've since done some experiments with Template Haskell, and I see  
that Arie Peterson has suggested how you could proceed. However, are  
you sure that you can't find a way to get this to work in vanilla  
Haskell without extensions? Or, for that matter, are you sure there  
isn't a way to get functional dependencies to work? (I felt pretty  
dumb for a little while before I found one for my problem, although  
as usual the issues are clear in hindsight.)


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


Re: [Haskell-cafe] let vs do?

2007-06-28 Thread Dave Bayer

On Jun 28, 2007, at 12:17 PM, Greg Meredith wrote:


Haskellians,

Once you have a polymorphic let, why do you need 'let' in the base  
language, at all? Is it possible to formulate Haskell entirely with  
do-notation where there is a standard monad for let environments?  
Probably this was all discussed before in the design deliberations  
for the language standard. Pointers would be very much appreciated.


Best wishes,

--greg


I've been wondering the same thing. When I want a break from coding,  
I rewrite files in an imaginary language to see what I want, what  
comes naturally. Let is the first keyword to go; a binding on one  
line followed by an expression on the next ought to imply a let/in  
combination.


Looking at special do language support for monads and arrows  
reminds me of special language support for tuples and lists. While it  
would probably be painful to lose all syntactic sugar, I would prefer  
a uniform mechanism for supporting any future construct like monads  
and arrows, so adding language support isn't restricted to the  
implementors. Monads and arrows are particular instances of a general  
functional programming idiom, and seeing how preciously they are  
treated reminds me of the early history of mathematical group theory,  
when people treated each of the few groups they knew as a one-off  
special case. No programming language should treat monads and arrows  
this way.


I'm struck by the readability requirement that leads to explicit  
= syntax, or adding language support. Readability should be a  
compiler option: You can't read someone else's code or your own weeks  
later? Have the compiler massively annotate the type information back  
into the code, supplying implied combinators, to a web page you can  
carefully study.


If one gets over a requirement that raw code be readable, then all  
sorts of combinators can be implied. Using type information, the  
compiler would be able to notice that two successive lines of code  
make no sense at all in sequence, but WOULD make perfect sense if a  
= was inserted. This is roughly what a do statement does, except a  
do statement does this in an ad hoc fashion for a very few combinators.


Rather than having a short ad-hoc list of operators inserted by do,  
analogous to the short ad-hoc list of syntactic sugar for tuples and  
lists, one could have a general class mechanism for inserting  
arbitrary combinators.


This would get confusing to read, but a compiler that could annotate  
code with explanations of what it did would help. Now, we're instead  
forced to write these annotations manually, and stare at them all of  
the time.

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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Dave Bayer

On Jun 22, 2007, at 3:11 PM, Brandon S. Allbery KF8NH wrote:

(1) any way to flag a pattern match as I know this is okay, don't  
warn about it without shutting off pattern match warnings completely?


GHC doesn't issue warnings about patterns on the left of =

For example, the following code compiles just fine with ghc -Wall - 
Werror, but the use of Just m generates a run-time exception:



module Main where

a :: [(Int,Int)]
a = [(2*n,n) | n - [1..100]]

m :: Int
Just m = lookup 3 a

main :: IO ()
main = putStrLn $ show m


I'd take this as a ghc feature, not a bug. When I use this construct  
in practice, I have a proof in mind that the pattern match cannot  
fail for my data, but I can't express the proof in Haskell's type  
system. I'm ok with skipping writing that proof.


The difference here is programmer intent. While a missing pattern  
case can often be an oversight, there's no way to put both cases here  
to the left of =, so the programmer clearly intends this code as  
written.


(An example of a language with a Turing complete type system is Qi:  
http://www.lambdassociates.org/
As pointed out elsewhere in this thread, it is unreasonable/ 
undecidable to expect a type system to work out arbitrarily difficult  
issues for you automatically. Some work is required, programming in  
the type system. They extend this point of view.)



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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Dave Bayer

On Jun 25, 2007, at 4:48 AM, Simon Peyton-Jones wrote:

The intention is that it should be straightforward to suppress  
warnings.


Simply add a type signature for 'z', or for the naked 3 in z's  
definition.


I constructed my example from larger modules peppered with small  
integer constants; such signatures would become a significant  
percentage of the code. I was hoping for a solution whose code size  
is at worst linear in the number of distinct integer constants used,  
not the number of times they are used. I'd like to avoid redefining  
operators if I can help it.


Given that there are entire languages in common use that don't  
support Integer, I don't see why ghc -Wall -Werror can't become  
such a language when it sees



default (Int)


Instead it issues defaulting warnings even in the presence of this  
declaration.


I couldn't find a way to add a type signature once for each small  
integer constant I plan to use; it would appear to me that



2,3 :: Int


by itself is not legal Haskell. The best I can do is to instead write


i2,i3 :: Int
(i2,i3) = (2,3)


which imposes a per-use penalty of one character per use, and is less  
readable than simply unrolling the constants in each use. In other  
words, if I can't write x^3, I find x*x*x more transparent than x^i3  
or x^(3::Int).


Despite my participation in a broader discussion, my hope in starting  
this thread was to understand how to most elegantly use the specific  
programming language ghc -Wall -Werror.


It continues to appear to me that ghc -Wall -Werror doesn't support  
small Int constants without a per-use penalty, measured in code length.


On Jun 25, 2007, at 4:48 AM, Simon Peyton-Jones wrote:
I think it matters what type is chosen, because it affects the  
output of the program; it's good practice to be explicit about what  
type you want, at each site where defaulting is applied.


I agree, so I'm glad I asked here rather than reporting warnings in  
the presence of default (Int) as a bug.


Unless I misunderstand and it is already possible, I'd now prefer a  
language extension that allows the explicit declarations



2,3 :: Int


once for each affected numeric literal.

 
___

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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Dave Bayer

On Jun 25, 2007, at 8:15 AM, Simon Peyton-Jones wrote:


i2 = 2 :: Int
i3 = 3 :: Int


The code


{-# OPTIONS_GHC -Wall -Werror #-}

module Main where

i2 = 2 :: Int
i3 = 3 :: Int

main :: IO ()
main = putStrLn $ show (i2,i3)


generates the errors


Main.hs:5:0: Warning: Definition but no type signature for `i2'
Main.hs:6:0: Warning: Definition but no type signature for `i3'


and imposes a linear per-use penalty of one extra character per use.  
If I can't write x^3, I find x*x*x more transparent than x^i3.


I know how to fix this; my previous message considered


i2,i3 :: Int
(i2,i3) = (2,3)


which still imposes a linear per-use penalty of one extra character  
per use.


It continues to appear to me that ghc -Wall -Werror doesn't support  
small Int constants without a per-use penalty, measured in code length.


Am I the only one blessed/cursed with a vision of how proponents of  
practical languages would have a field day with this? Perhaps I'm  
reading too many blogs.


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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Dave Bayer


On Mon, Jun 25, 2007 at 07:31:09PM +0100, Ian Lynagh wrote:


I don't know if (^) in particular is what is causing you problems, but
IMO it has the wrong type; just as we have
(!!) :: [a] - Int - a
genericIndex :: (Integral b) = [a] - b   - a
we should also have
(^)  :: (Num a) = a - Int - a
genericPower :: (Num a, Integral b) = a - b   - a


On Jun 25, 2007, at 11:40 AM, David Roundy wrote:


That would be great!


Ahh, a consensus I can enthusiastically support.

It would seem to me a good library design rule of thumb to make ANY  
argument that will be counted down to zero by simple recursion an  
Int, with the type of (^) a standard application of this general  
principle.


Even with strict evaluation and tail recursion, if I want to write  
something that's going to need more than 2^31 iterations, I want the  
compiler to make me jump through hoops to say so. With the current  
type for (^), I'm jumping through hoops to say something that I can  
more easily unroll by hand.


Your proposal for (^) would allow genericPower to use the  
asymptotically faster algorithm of writing out the exponent in binary  
and multiplying together repeated squares, leaving the simple  
recursion to (^).

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


[Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Dave Bayer

Hi all,

I've been going over my code trying to get it all to compile with  
ghc -Wall -Werror, without introducing constructs that would make  
my code the laughing stock of the dynamic typing community. They  
already think we're nuts; my daydreams are of a more computer  
literate society where Jessie Helms stands up in the U.S. Senate to  
read aloud my type declarations to the derisive laughter of the Ruby  
and Lisp parties.


There's a fine line between my opinion as to how GHC should issue  
warnings, and a legitimate bug report. I've already submitted a bug  
report for the need to declare the type of the wildcard pattern,  
because I believe that the case is clear. Here, I'm seeking guidance.  
Perhaps I just don't know the most elegant construct to use?


My sample code is this:



{-# OPTIONS_GHC -Wall -Werror #-}

module Main where

import Prelude hiding ((^))
import qualified Prelude ((^))

default (Int)

infixr 8 ^
(^) :: Num a = a - Int - a
x ^ n = x Prelude.^ n

main :: IO ()
main =
   let r = pi :: Double
   x = r ^ (3 :: Int)
   y = r ^ 3
   z = r Prelude.^ 3
   in  putStrLn $ show (x,y,z)



GHC issues a Warning: Defaulting the following constraint(s) to type  
`Int' for the definition of z.


The definition of y glides through, so a qualified import and  
redefinition of each ambiguous operator does provide a work-around,  
but the code is lame. (I could always encapsulate it in a module  
Qualude.)


If I import a module that I don't use, then ghc -Wall -Werror  
rightly complains. By analogy, if I use default (Int) to ask GHC to  
default to Int but the situation never arises, then GHC should  
rightly complain. Instead, if I use default (Int), GHC complains  
about defaulting anyways. In my opinion, this is a bug, but I'd like  
guidance before reporting it. Is there a more elegant way to handle  
the numeric type classes with ghc -Wall -Werror ?


No one is forced to use ghc -Wall -Werror, but it should be a  
practical choice.


I've enjoyed the recent typing discussions here. On one hand, there's  
little difference between using dynamic typing, and writing  
incomplete patterns in a strongly typed language. On the other hand,  
how is an incomplete pattern any different from code that potentially  
divides by zero? One quickly gets into decidability issues, dependent  
types, Turing-complete type systems.


My personal compromise is to use ghc -Wall -Werror, live with the  
consequences, and get back to work. Perhaps I'll get over it, but  
that's a slippery slope back to Lisp.


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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Dave Bayer

On Jun 22, 2007, at 11:42 AM, David Roundy wrote:


On Fri, Jun 22, 2007 at 11:37:15AM -0700, Dave Bayer wrote:

GHC issues a Warning: Defaulting the following constraint(s) to type
`Int' for the definition of z.


Why don't you just use -fno-warn-type-defaults?

...

ghc -Werr -Wall is a often good idea, but if you prefer a different
programming style (e.g. no top-level type declarations required),  
ghc gives

you the flexibility to do that.


To be precise, I __PREFER__ a ghc  -Wall -Werror programming style.  
In particular, I always want defaulting errors, because sometimes I  
miss the fact that numbers I can count on my fingers are defaulting  
to Integer.


Once I explicitly declare default (Int), I want ghc  -Wall - 
Werror to shut up, unless this defaulting rule never gets used.  
Instead, it complains anyways when the defaulting takes place that  
I've just declared I know about. In other words, I want warnings  
involving default to follow the same logic currently used for  
warnings involving import.


This is a bug. I want ghc  -Wall -Werror to be a practical choice,  
left on all the time, and in my example I had to work too hard to  
avoid the warning. Other people just wouldn't use ghc  -Wall - 
Werror, the way some people won't use seat belts, and the way some  
people view any strongly typed language as a cumbersome seat belt. If  
we tolerate ridiculously arcane syntax to handle these situations, we  
fully deserve to be marginalized while Ruby takes over the world.


In other words, I'm disputing that the top-level declarations are in  
fact required. GHC can be trivially modified to allow Haskell to  
handle this situation far more elegantly.


(It is amusing the sides we're taking on this, and the stereotype  
that physicists compute faster than mathematicians because they don't  
worry about convergence issues. Effectively, the stereotype holds  
that mathematicians think with -Wall -Werror on, and physicists  
don't. Perhaps it's true?)



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


[Haskell-cafe] Compile-time here document facility

2007-06-22 Thread Dave Bayer
I couldn't find a compile-time here document facility, so I wrote one  
using Template Haskell:



module HereDocs(hereDocs) where

import Control.Exception
import Language.Haskell.TH.Syntax

getDoc :: String - [String] - (String,[String])
getDoc eof txt =
let (doc,rest) = break (== eof) txt
in  (unlines doc, drop 1 rest)

makeVal :: String - String - [Dec]
makeVal var doc = let name = mkName var in
[SigD name (ConT (mkName String)),
ValD (VarP name) (NormalB (LitE (StringL doc))) []]

scanSrc :: [Dec] - [String] - Q [Dec]
scanSrc vals [] = return vals
scanSrc vals (x:xs) = case words x of
[var, =, ('':'':eof)] -
let (doc,rest) = getDoc eof xs
val = makeVal var doc
in  scanSrc (vals ++ val) rest
_ - scanSrc vals xs

hereDocs :: FilePath - Q [Dec]
hereDocs src =
let fin = catchJust assertions (evaluate src) (return.takeWhile  
(/= ':'))

in  runIO (fin = readFile = return . lines) = scanSrc []


One binds here documents embedded in comments by writing


import HereDocs
$(hereDocs Main.hs)


As an idiom, one can refer to the current file as follows; the first  
thing hereDocs does is catch assert errors in order to learn the file  
name:



import HereDocs
$(hereDocs $ assert False )


Here is an example use:


{-# OPTIONS_GHC -fth -Wall -Werror #-}

module Main where

import System
import Control.Exception

import HereDocs
$(hereDocs $ assert False )

{-
ruby = RUBY
#!/usr/bin/env ruby
hello = EOF
Ruby is not
   an acceptable Lisp
EOF
puts hello
RUBY

lisp = LISP
#!/usr/bin/env mzscheme -qr
(display #EOF
Lisp is not
   an acceptable Haskell
EOF
)
(newline)
LISP
-}

exec :: FilePath - String - IO ExitCode
exec fout str = do
   writeFile fout str
   system (chmod +x  ++ fout ++ ; ./ ++ fout)

main :: IO ExitCode
main = do
   exec hello.rb ruby
   exec hello.scm lisp



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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Dave Bayer

On Jun 22, 2007, at 2:46 PM, David Roundy wrote:

I think of top-level type declarations as type-checked comments,  
rather
than a seat-belt.  It forces you to communicate to others what a  
function
does, if that function may be used elsewhere.  I like this.   
Although it can
be cumbersome for quick and dirty code, developers trying to read  
your code
will thank you for it (unless you make *everything* top-level,  
which is

just poor coding style).

-Wall -Werror isn't a seat belt, it's a coding-style guideline.


I don't think one can make blanket statements as to what type systems  
are for. I doubt that the people who've dedicated their lives to  
type theory are doing so to provide style guidelines.


I like the quick and open-ended definition that types are compile- 
time proxies for run-time values. It happens that current type  
systems are closely tied to propositional logic, because so many  
logicians are drawn to the work. This need not be the case.


From this point of view, one pays attention to type theory because  
one produces the best code by providing the best guidance to the  
compiler. -Wall -Werror is establishing a contract to do so.


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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Dave Bayer

On Jun 22, 2007, at 12:34 PM, Dave Bayer wrote:

In particular, I always want defaulting errors, because sometimes I  
miss the fact that numbers I can count on my fingers are defaulting  
to Integer.


So no one took the bait to actually offer me a shorter idiom, but I  
thought about the above sentence, and had a big Homer Simpson Doh!  
revelation. In the acual code I was cleaning up, just write out the  
exponentiations, for example,



evalBezier :: R - Bezier - [R]
evalBezier t b = let s = 1-t in case b of
Line x y - s*.x .+. t*.y
Cubic w x y z - s*s*s*.w .+. 3*s*s*t*.x .+. 3*s*t*t*.y .+.  
t*t*t*.z


To my taste, that's much prettier than half a dozen lines of  
declarations to get ^ to behave with ghc -Wall -Werror, and after all  
I'm just hand-unrolling the code for ^.

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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-22 Thread Dave Bayer

On Jun 22, 2007, at 4:37 PM, David Roundy wrote:


You get strongly-typed code whether or not you enable warnings.


In my opinion it's delusional to think one is using strong typing if  
one doesn't enable warnings. All the puffing about the advantages of  
strong typing look pretty silly if code hangs up on an incomplete  
pattern. Let's remember that the other side of this debate is rather  
eloquent, be it Paul Graham or a Ruby enthusiast. People who don't  
worry so much about types believe that they get things done. Is using  
a strongly typed language like buying a hybrid car, it costs too much  
but you're helping with maybe someday...?


I refuse to drink the Kool-Aid and recite precisely what I'm told a  
type is in June, 2007; I'm hoping that types will evolve by the time  
I die. For types to evolves, we need to step back a few feet and  
think more loosely what a type really is.


If someone writes working code with incomplete patterns, they're  
effectively using a dependent type without being able to say so in  
Haskell. They're using a specialization of the type they claim to be  
using, in which the missing patterns are never needed. Filling in with


	_  - error I'm sweeping this under the rug so it's no longer the  
type system's problem


just highlights the inadequacy of the type system. The code hangs  
either way, if the belief that this case doesn't happen is wrong. I'm  
more of a Will the code hang or not? kind of guy than Will I be  
kicked out of the tree house if I use the wrong words for things?  
kind of guy. The missing pattern that shouldn't happen is abstractly  
a type issue, whether we can get the compiler to lay off or not.


Similarly, the whole defaulting debate is good form/bad form  
considerations for how best to use types to automatically write code  
for us.


It all comes back to what I said before, types are compile-time  
proxies for run-time values. I'm nudging at compile-time, therefore  
I'm messing with types, not values.


If I go away and write in Lisp or Ruby, then return to Haskell with  
ghc -Wall -Werror, it is glaringly obvious to me that the nudging I  
have to do to get things to work with warnings on has to do with  
types. I truly don't mind the nudging, it is very educational, but  
let's call a spade a spade?





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