Effect of large binaries on garbage collection

2003-03-04 Thread Adrian Hey
Hello,

I'm writing a library which will require many blocks of binary data
of various sizes (some very large) to be stored in the heap. I'm a
little worried about the effect this will have on the efficiency of
garbage collection. I'm not sure how ghc gc works these days, but
I seem to remember it's a copying collector by default. If so it seems
a pity to waste time copying 10's of MBytes of binaries at each
collection.

The options I'm considering are..

(1) Use Haskell heap space
Pros: Easy for me
Cons: May slow down gc
  AFAICS I can't use anything like realloc
  Current FFI proposals seem to prevent me from directly
  accessing Haskell heap objects from C land (or have I
  misunderstood?).

(2) Use C heap space
Pros: Easy(ish) to use from C and Haskell ffi
Cons: Unless C heaps have improved a lot since I last looked
  (which I doubt), it seems likely I will suffer from slow
  allocation and fragmentation problems. 

(3) Write my own sliding heap manager and use finalisers for
   garbage collection.
   Pros: Can tailor it to work exactly the way I want.
   Cons: More work for me, especially if I want the
 result to be portable across OS's. 
 Might be a complete waste of time if my worries
 about ghc heap management are groundless :-)

Any advice?

Thanks
--
Adrian Hey
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Effect of large binaries on garbage collection

2003-03-04 Thread Simon Peyton-Jones
GHC does not copy big objects, so don't worry about the copying cost.
(Instead of copying, it allocates big objects to (a contiguous series
of) heap blocks, with no other objects in those blocks.  Then the object
can move simply by swizzling the heap-block descriptor.)

Simon

| -Original Message-
| From: Adrian Hey [mailto:[EMAIL PROTECTED]
| Sent: 04 March 2003 11:05
| To: [EMAIL PROTECTED]
| Subject: Effect of large binaries on garbage collection
| 
| Hello,
| 
| I'm writing a library which will require many blocks of binary data
| of various sizes (some very large) to be stored in the heap. I'm a
| little worried about the effect this will have on the efficiency of
| garbage collection. I'm not sure how ghc gc works these days, but
| I seem to remember it's a copying collector by default. If so it seems
| a pity to waste time copying 10's of MBytes of binaries at each
| collection.
| 
| The options I'm considering are..
| 
| (1) Use Haskell heap space
| Pros: Easy for me
| Cons: May slow down gc
| AFAICS I can't use anything like realloc
|   Current FFI proposals seem to prevent me from directly
|   accessing Haskell heap objects from C land (or have I
|   misunderstood?).
| 
| (2) Use C heap space
| Pros: Easy(ish) to use from C and Haskell ffi
| Cons: Unless C heaps have improved a lot since I last looked
|   (which I doubt), it seems likely I will suffer from slow
|   allocation and fragmentation problems.
| 
| (3) Write my own sliding heap manager and use finalisers for
|garbage collection.
|Pros: Can tailor it to work exactly the way I want.
|Cons: More work for me, especially if I want the
|  result to be portable across OS's.
|  Might be a complete waste of time if my worries
|  about ghc heap management are groundless :-)
| 
| Any advice?
| 
| Thanks
| --
| Adrian Hey
| ___
| Glasgow-haskell-users mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Stack profiling

2003-03-04 Thread Wolfgang Thaller
I had wanted to CC this to the list, but of course I forgot:

Stephen Pitts [EMAIL PROTECTED] wrote:
Is there an easy way to profile stack usage without rebuilding with 
ticky-ticky profiling? I have two implementations of an algorithm; 
the one with straight lists seems to use constant stack, while the 
one with a JoinList is eating up stack at an O(n) rate.
No idea. I haven't used all features of the profiler yet. I'm taking 
the liberty of CCing the [EMAIL PROTECTED] mailing 
list, I hope somebody else can provide an answer.

If not, could I have your build script to generate a MacOS X package 
for a rebuilt GHC with ticky-ticky libraries? No matter what I do, 
all roads lead to rebuilding from source ;-).
There's no build script for making Mac OS X packages - I need to use 
Apple's GUI tools to create the package, and the rest is a relatively 
simple matter of configure and make.
You'd have to download the source, create a build.mk file saying that 
you want ticky-ticky profiling, and then configure, make and make 
install...

Cheers,

Wolfgang

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: First-class types

2003-03-04 Thread Simon Peyton-Jones
| The following is a more flexible alternative to overloading. We
| essentially define a function on types and invoke it, seemingly at run
| time. No Dynamics or unsafe computations are employed. We only need
| existential types, multi-parameter classes and functional
| dependencies. The code also shows how to manipulate values which
| cannot be manipulated.

Ingenious, but unnecessarily complicated. You don't need existential
types at all.
(See the code below, which is considerably simpler and, I fancy, a bit
more efficient.)  Also, I'm not sure why you make 'Type' (which is
pretty much the Typable class in the Dynamic library) into a superclass
of D; it's not used.  The idea of using a value (which is never
evaluated) as a proxy for a type is exactly what the Typable class does.
Indeed, it is a really useful technique.

The clever things about your solution are

a) You avoid the nasty ambiguity trap that many such schemes fall into
e.g. when you see (a + b) * (c-d), what is type are the 
intermediate values (a+b) and (c-d).   You drive the type of the result
from the type of the arguments, which makes sense.  (Albeit, if you you
want to add two Floats and get an Int, you'll have to do a conversion at
the end.)

b) You separate the coercion stuff from the operations in a nice way.

Simon


class D a1 a2 b | a1 a2- b where
  typeof :: a1 - a2 - b
 
instance D Bool Bool Int
instance D Int Bool Int
instance D Bool Int Int
instance D Int Int Int
instance D () Int Int
instance D Int () Int
instance D () () Int
instance D Int Float Float
instance D () Float Float
instance D Float Int Float
instance D Float Float Float

-- The coercion function

class Coerce a b where
coerce :: a - b - b
  
instance Coerce () Int where
coerce _ _ = 0

instance Coerce () Float where
coerce _ _ = 0

instance Coerce Int Int where
coerce = const

instance Coerce Float Float where
coerce = const

instance Coerce Int Float where
coerce x _ = fromInteger $ toInteger x
 
instance Coerce Bool Int where
coerce True _ = 1
coerce False _ = 0

add x y = let general_type = typeof x y
  x' = coerce x general_type
  y' = coerce y general_type
  in x' + y'

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: fundeps for extended Monad definition

2003-03-04 Thread Simon Peyton-Jones
| I believe something along the lines of the following would work:
| 
|  class C a b | a - b where { foo :: b - String }
|  instance C Int Int   where { foo x = show (x+1) }
|  x :: forall b. C Int b = b
|  x = 5
| 
| (Supposing that the above definition were valid; i.e., we didn't get
the
| type signature error, this reads that x has type b for all types
| b such that C Int b -- the fact that there is only one such type
(due to
| the fun dep) is for us to know.)
| 
| Then, we should be able to say:
| 
|  foo x
| 
| and get 6.

I understand that is what you would like, but I do not know how to
achieve it in a reasonable way.  (By reasonable I mean both in terms
of a reasonably simple type inference algorithm, and in terms of a
reasonable translation into a typed intermediate language.  The latter
is, in a sense, just an implementation matter, but I have found it to be
an excellent sanity check.)

Simon

| 

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: Persistent data

2003-03-04 Thread Simon Peyton-Jones
GHC has a multi-generational garbage collector.  If you have enough
physical memory on your machine so that the GC isn't thrashing trying to
find the 100 free bytes that remain, then you should find the database
migrates to the oldest generation and stays there.  If you use +RTS
-Sstderr you'll see info about when GC happens, and which generation.
There should be lots of young-gen collections for each old-gen one. You
can increase the number of generations with a command-line flag to the
runtime system (see the user manual).   

Simon

| -Original Message-
| From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED]
| Sent: 03 March 2003 18:38
| To: [EMAIL PROTECTED]
| Subject: Persistent data
| 
| Is there some way to reduce the cost of garbage collection over large
persistent
| datastructures without resorting to escaping to C to malloc memory
outside the
| heap?
| 
| The program I'm working is part database, which cannot discard
information.
| The net result is that I see figures like 82.9% of the time taken by
garbage
| collection. The heap profile looks like a charging capacitor: a linear
increase
| (as expected) which is slowly dilated as time increases by the garbage
collector
| thrashing memory.
| 
| When I worked on the LOLITA natural language processor we solved the
problem
| by moving a lot of the data out to C++, so that the heap only contains
things
| soon to be freed. I know generational garbage collection is supposed
to help,
| but it doesn't seem to. Is there a pure Haskell solution to this
problem?
| 
| Sengan
| 
| ___
| Haskell mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/haskell
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Parsec: GHC /= Hugs?

2003-03-04 Thread Markus . Schnell
My program has a different behaviour under hugs and ghc.

I wrote a very simple parser with Parsec and it parses a file quite easily -
as long as
I use hugs to run it. But when I compile it with ghc, the parse fails.
(I'm currently working on WinNT with cygwin).

Something else, but related: how do I avoid writing different Code for Hugs
and ghc?
For example, I had to hide Word in Hugs with 
 import Prelude hiding (Word)
but was not allowed to do that with ghc. I ended up using Wort.

Why the difference?

Markus

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: First-class types

2003-03-04 Thread Jan-Willem Maessen
Simon PJ replies:
 Ingenious, but unnecessarily complicated. You don't need existential
 types at all.
 (See the code below, which is considerably simpler and, I fancy, a bit
 more efficient.)  Also, I'm not sure why you make 'Type' (which is
 pretty much the Typable class in the Dynamic library) into a superclass
 of D; it's not used.  The idea of using a value (which is never
 evaluated) as a proxy for a type is exactly what the Typable class does.
 Indeed, it is a really useful technique.

I agree.  I like it when this sort of thing can be reduced to just a
few lines of code.

I suspect it is possible to turn coerce and/or typeof into some
sort of asTypeOf-like operator and avoid the creation of undefined
proxies for the result type.  Indeed, perhaps we want a definition
such as this (untested, but probably subtly wrong):

 class (Coerce a1 b, Coerce a2 b) = D a1 a2 b | a1 a2 - b where
   lift2 :: (b - b - b) - a1 - a2 - b
   lift2 op = op'
 where op' a b = op (coerce a) (coerce b)
 
 class Coerce a b where
   coerce :: a - b
 
 -- lots of instances here.
 
 add = lift2 (+)
 sub = lift2 (-)

In general, if D is being used only to define coercions on a binary
operation, thenin my opinion the class method ought to be a coercion
on a binary operation.

But I had a couple of questions for the avid type-hackers out there,
motivated by this example and by similar examples from my own
tinkerings:

1) Coerce a a can be defined as coerce=id for all a.  However, this
   may of course lead to overlap in the type structure, so we must
   write a separate instance definition for Coerce Int Int, Coerce
   Double Double, etc. if we want types to be decidable.  I'd love for
   some clever person to solve this little difficulty.

2) When we define D a b c, we know that D b a c is also allowed.
   Again, decidability prevents us from asserting this directly.
   Again, a clever solution could save us a lot of code and even more
   debugging.  I suspect this may be a marginally easier nut to crack
   than the previous one.

So, type hackers, can you come up with a Byzantine set of classes
which encode these restrictions nicely and decidably?

-Jan-Willem Maessen

[Note that I suspect that it maybe possible to *prove* that you can't,
at least for case 1.  If you're really ambitious, you might want to
attack transitivity of coercion, too.]
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Tutorial for literate Haskell

2003-03-04 Thread Steffen Mazanek
Hi,

 When I ran into the same question some time ago I tried that,
 but found that the \verbatim was interpreted to0 literally, so
 that the \end{code} does not terminate it. Could you give a 
 complete short example that works for you?
 
 My own solution was to copy the definition of verbatim from the 
 base files, and define code the same way in a separate style file.

Hmm, there were no problems in simply doing so.

MainFile.tex:

\documentclass[12pt,oneside]{report}
\usepackage[latin1]{inputenc}
\usepackage{verbatim}
\begin{document}
\newenvironment{code}{\footnotesize\verbatim}{\endverbatim\normalsize}
\begin{titlepage}
...
\begin{document}
...
\input{HaskellModule.lhs}
...



HaskellModule.lhs:

\chapter{The Module Foo}
\label{Foo}
Maybe some text...
We call our module Foo, because this name is very
meaningful.
\begin{code}
module Foo where
\end{code}
and so on

Thats it.
I hope this will help.

Ciao,
Steffen


-- 
Steffen Mazanek
Werner Heisenberg Weg 102 App. 232
85579 Neubiberg

GPG key fingerprint: A165 227D B288 5E10 701D  BF5F E91C 6B88 24C8 397D
http://blackhole.pca.dfn.de:11371/pks/lookup?op=getsearch=0x24C8397D
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Parsec: GHC /= Hugs?

2003-03-04 Thread Johannes Waldmann
On Tue, 4 Mar 2003 [EMAIL PROTECTED] wrote:

 My program has a different behaviour under hugs and ghc.
 I wrote a very simple parser with Parsec and it parses a file quite easily -

I once got bitten by this:

brackets is now called angles, while squares is now called brackets.

see http://www.cs.uu.nl/~daan/parsec.html

-- 
-- Johannes Waldmann  http://www.informatik.uni-leipzig.de/~joe/ --
-- [EMAIL PROTECTED] -- phone/fax (+49) 341 9732 204/207 --

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


big lambda in class declarations

2003-03-04 Thread Hal Daume III
So the word on the street is that allowing big lambda makes type inference
undecidable.  This makes sense to me since allowing big lambda essentially
allows you to program at the type level and thus of course you'll get
undecidability.

However, I'm having difficulty understanding where the undecidability
sneaks in if you allow big lambda in class declarations.  I suppose the
cannonical example is when you want to write something like:

 class Set s where { ... }
 instance Set (/\ a. FiniteMap a ()) where { ... }

but now you have to write:

 data FMSet a = FMSet (FiniteMap a ())
 instance Set FMSet where { ... }

The big lambda is of course equivalent to not applying type synonyms
completely, somethign like:

 type FM a = FiniteMap a ()
 instance Set FM where { ... }

will of course also be rejected (since this would give us a way to do big
lambda).

Could some one help my intuition a bit here and explain to me how you
could use big lambdas in class declarations to write programs?

Thanks!

 - Hal

--
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Parsec: GHC /= Hugs?

2003-03-04 Thread Iavor S. Diatchki
hi,

[EMAIL PROTECTED] wrote:
Something else, but related: how do I avoid writing different Code for Hugs
and ghc?
For example, I had to hide Word in Hugs with 
 ...

you are not allowed to hide things that are not exported.
hugs erroneously used to export Word (and other stuff) from the prelude.
i am glad to say that this is not the case anymore (in the CVS version). 
 actually when using the CVS hugs nearly all programs that run in GHC
run in hugs as well (Haskell 98 anyways, but even a lot of the other 
stuff matches).   if you find differences (for the haskell 98 part) you 
should identify which of the two you think is doing something wrong and 
report it as a bug.

bye
iavor
--
==
| Iavor S. Diatchki, Ph.D. student   |
| Department of Computer Science and Engineering |
| School of OGI at OHSU  |
| http://www.cse.ogi.edu/~diatchki   |
==
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Persistant (as in on disk) data

2003-03-04 Thread Iavor S. Diatchki
hello,

a recent post reminded me of a feature i'd like.
for all i know it is already implemenetd in GHC so pointers are welcome.
i'd like to be able to dump data structures to disk, and later load 
them.  currently i do that with Show/Read but it is very slow and it 
seems as a kind of ovarloaded use fo Show. and it doesn't work with 
circular structures.  so i'm thinking something like deriving 
Persistant.  for functions perhaps the easiest thing is to leave it to 
the user to create the instances.  perhaps:

class Persistant t where
  save :: t - String - IO ()
  load :: String - IO t
here the String is the name of the file where to store/load the data.

so is there such a thing already, and if not would it be difficult to 
add to say GHC?

bye
iavor


--
==
| Iavor S. Diatchki, Ph.D. student   |
| Department of Computer Science and Engineering |
| School of OGI at OHSU  |
| http://www.cse.ogi.edu/~diatchki   |
==
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


compiling

2003-03-04 Thread Mike T. Machenry
I am having a problem compiling my code. Usually I run it with
ghci -package data -fglashow-exts Main.hs

Main declares a main function and imports all my other files.
when I try to ghc it to compile I get that it can't find an interface file
for each file in my project. How do I compile something? Also it can't
find an interface for Data. How do I make an interface file for that?

Thanks,
-mike
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: compiling

2003-03-04 Thread Matthew Donadio
Mike T. Machenry wrote:
 I am having a problem compiling my code. Usually I run it with
 ghci -package data -fglashow-exts Main.hs
 
 Main declares a main function and imports all my other files.
 when I try to ghc it to compile I get that it can't find an interface file
 for each file in my project. How do I compile something? Also it can't
 find an interface for Data. How do I make an interface file for that?

Read the ghc docs, but try

ghc -o Main --make -package data -fglashow-exts Main.hs

-- 
Matthew Donadio ([EMAIL PROTECTED])
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: int to float problem

2003-03-04 Thread Andrew J Bromage
G'day all.

On Mon, Mar 03, 2003 at 12:10:28PM -0500, Matthew Donadio wrote:

 This is my biggest gripe with Haskell, at least for what I do.  The
 numeric class system is good, but it assumes that the sub-classes are
 distict, where in fact integers are a proper subset of reals, which
 are a proper subset of complex numbers.

Haskell Integers are not a proper subset of Haskell Floats or
Doubles.  Haskell does not support real numbers.

It's a similar problem with C/C++.  The long type is almost never
a proper subset of float, but C will nevertheless happily convert
it for you without you asking, potentially losing precision in the
process.

Cheers,
Andrew Bromage
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: Network module problem

2003-03-04 Thread Simon Marlow
 Hello.  I'm running into a problem with the Network module, 
 which I suspect
 is pretty easy to fix, but am not sure how to best do so.
 
 The problem is that accept fails when the reverse DNS 
 fails, with the
 following error:
 
 Fail: does not exist
 Action: getHostByAddr
 Reason: no such host entry
 
 I'm not sure how to get around this.  I don't actually need 
 the hostname of
 the client, and would be happy to just substitute its IP 
 address in that field, but I'm not sure how to do that.

We've made this change in the library, the next release of GHC will
include the fix.  Unfortunately there's no immediate workaround, other
than using the Network.Socket interface to accept (which isn't hard, the
Network.accept wrapper is fairly simple).

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


Re: speedup help

2003-03-04 Thread Damien R. Sullivan
On Mon, Mar 03, 2003 at 08:46:22PM -0800, Mark P Jones wrote:

  pascal :: [[Integer]]
  pascal  = iterate (\row - zipWith (+) ([0] ++ row) (row ++ [0])) [1]
 
  comb:: Int - Int - Integer
  comb n m = pascal !! n !! m

 In that case, you can take further advantage of using Pascal's triangle
 by recognizing that numbers of the form (comb (n+1) i) are just the
 entries in the (n+1)th row.  (All but the last two, for reasons I
 don't understand ... did you possibly want [0..n+1]?)  So we get the

No, the sum for a Bernoulli number is a combination times another Bernoulli
number from 0 to n-1.  Hard to have B_n depend on B_n.  At least in a nice
recurrence...

   sumbn n = sum [ bernoulli i * fromIntegral c
 | (i,c) - zip [0..n-1] (pascal!!(n+1)) ]

This code as is takes about 23 seconds, comparable to the 22 seconds of
factorial with array (hardcoded, since I can't get it dynamically in a pretty
fashion.)  If I turned pascal into arrays it might be even faster.  I'd have
to change something though, right, zipWith wouldn't work with arrays?

 Actually, I prefer the following version that introduces an explicit
 dot product operator:
 
   sumbn n = take n (map bernoulli [0..]) `dot` (pascal!!(n+1))
   dot xs ys = sum (zipWith (*) xs ys)

This needed some modification, since bernoulli returns Rationals, so I had
zipWith use a special mult function.  It just took 25 seconds.

 slower, I thought these definitions were interesting and different
 enough to justify sharing ...

Hey, you're even faster too!  At least for messing with comb.

Aaron Denney, to his credit, had a pretty similar idea a week ago, but I
didn't get what he was talking about then.  Newbies like code they can paste
in. :)

Thanks!

-xx- Damien X-) 


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


Re: is identity the only polymorphic function without typeclasses?

2003-03-04 Thread Jay Cox
 The time you grouped (a-b-c), you utilized the arrow type constructor to
 build a function type, it is no different that using a polymorphic list. I
 think I am not happy with the dual semantics of this arrow thingie. I have
 to ponder on this some more, I guess.

 Thanks for the response. Greatly appreciated.

I'm not a student of type theory, but what follows is my own attempt to
rigorously (per my definitions) formalize an answer.

Lets forget about the undefined, bottom, error, or whatever cases and look
at the following.

Lets think about this inductively.
First off, lets start off with something of type a. (here we don't mean that
something
of type forall a . a, which is a whole different type, we just mean we have
something with a specific type, we just don't care what it is.)

Now, with the arrow constructor we can build two new types of functions.
a -  a  (of which the only useful function I can see is id or a constant
function
which constrains the type of the 1st argument.)
b -  a   (which is  basically a constant function.)
we can continue to build new functions by either adding an existing type
variable
from the list of expressions we have created, or introducing the new type
variable c.

so now we have

U: a - a - a
V: a - b - a
W: b - a - a
X: b - b - a
Y: c - a - a
Z: c - b - a

Analyzing the functions (U..Z) we find:
U: could be any any thing similar to asTypeOf  (selecting either the first
or second arguments, constraining them to a single type,) or a constant
valued function.
V: choose first argument or constant
W: choose second argument or constant.
X: constant f (But could this be a very odd but perhaps minorly useful
method to constrain types of certain values in some type system?) Lets call
this a constant asTypeOf function
Y: whoops! this is isomprophic to W
Z: constant f

Now, if we go on creating 3,4,...,N parameter, etc. functions, could we find
anything other than functions which could not described described  as some
combination of the following? (Assume i is integer and z_i is just a
specific argumetn number).
1: selecting asTypeOf function
(with type constraint a on arguments (y_1,y_2, ...),
 type constraint b on arguments (z_1,z_2, ),
 type constraint c )
I am considering id as one of these, since it selects its first (and
only) argument.
2: constant asTypeOf function
with type constraints similar to that of case 1.
3: constant function without type constraints.

This is where induction can get confusing, because we need to deal with  6
cases.
existing type var on cases 1,2, and 3, and new type var on cases 1,2,and 3.
I will denote the cases et1,et2,et3 and nt1,nt2,nt3 respectively.
et1: just (possibly*) adds a new type constraint to new function
et2: just (possibly*) adds a new type constraint to new function
et3: now we have a constraint on the type, so the new function is a case 2
function.
nt1: no new type constraint
nt2: no new type constraint
nt3: no new type constraint (Th new function is a constant function without
type constraints).

* I say possibly here because in the case where you selected a type var
amongst the set of type vars which are already declared in your list of
created functions, and add
it to a function which does not have that type var, it would be the same as
adding a new type var. If this is confusing, just consider cases W and Y a
from few paragraphs above (where meantion, whoops, this is isomorphic...)
and maybe you'll understand what I'm trying to say.

So it looks like you only get those three cases if you go by my partitioning
of the kinds of functions.

Jay Cox

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