Re: Typesafe MRef with a regular monad

2003-06-13 Thread Carl R. Witty
Keith Wansbrough [EMAIL PROTECTED] writes: In article [EMAIL PROTECTED], [EMAIL PROTECTED] (Carl R. Witty) wrote: Here's a hand-waving argument that you need either Typeable (or something else that has a run-time concrete representation of types) or ST/STRef (or something else

Re: Typesafe MRef with a regular monad

2003-06-12 Thread Carl R. Witty
Simon Peyton-Jones [EMAIL PROTECTED] writes: | Conjecture: It's impossible to implement RefMonad directly in Haskell | without making use of built-in ST or IO functionality and without unsafe or | potentially diverging code (such as unsafeCoerce). A more concrete way to formulate a problem

Re: thread blocked indefinitely

2003-06-06 Thread Carl R. Witty
Simon Marlow [EMAIL PROTECTED] writes: I'm now `GHC.Conc.forkProcess`ing only from the initial thread, and all seems well. Thanks for the suggestion! Any idea when `forkProcess` might get fixed? Don't hurry on my account; I'm just curious. There's a comment in the code from

Re: Field labels must be globally unique?

2003-01-14 Thread Carl R. Witty
Marc Ziegert [EMAIL PROTECTED] writes: It would be nice to be able to overload class-functions like classes: instance (+), (-) - Vector where (+) v1 v2 = ... (-) v1 v2 = ... instead of overloading parts of a class... (because of

Re: The Haskell 98 Report

2002-12-03 Thread Carl R. Witty
Claus Reinke [EMAIL PROTECTED] writes: So, as a small token, I've revised my original plan and will now buy one of the printed versions (I shall also place higher priority on submitting to JFP in the future;-). Let's support forward-looking publishers! Thanks, Simon, and thanks, Conrad

Re: GetMBlock: misaligned block

2002-09-11 Thread Carl R. Witty
Simon Marlow [EMAIL PROTECTED] writes: The problem is that GHC is asking for memory at a particular address (0x5000) and the kernel is returning memory elsewhere that doesn't satisfy our aligment constraints (1M aligned). We don't particularly care where we get memory from, but it must

Re: typeclass relations

2002-09-11 Thread Carl R. Witty
S.M.Kahrs [EMAIL PROTECTED] writes: The class checker for the above is like a little Prolog program: foo(int). bar(int). foo(char). bar(X) :- foo(X). So, the type system for C++ lets you encode (some) Haskell programs and the type system for Haskell lets you encode (some) Prolog

Re: problems with FFI including h files

2002-06-10 Thread Carl R. Witty
Alastair Reid [EMAIL PROTECTED] writes: I thought we established that generating valid C prototypes from the Haskell FFI type signature wasn't possible due to the incompleteness of the Haskell type (lack of 'const' modifiers for one thing - is there anything else?). Compilers use the

Re: Strictness!

2002-03-18 Thread Carl R. Witty
Jay Cox [EMAIL PROTECTED] writes: On Thu, 14 Mar 2002, Brian Huffman wrote: In Haskell you can produce the desired behavior by using pattern guards. Since the pattern guards always get evaluated before the result does, they can be used to make things more strict. Here is the foldl

Re: H98 Report: expression syntax glitch

2002-03-01 Thread Carl R. Witty
Simon Peyton-Jones [EMAIL PROTECTED] writes: I didn't phrase it right. I meant that a let/lambda/if always extends to the next relevant (not part of a smaller expression) punctuation symbol; and if that phrase parses as an exp that's fine, otherwise it's a parse error. So I should not

Re: syntax...(strings/interpolation/here docs)

2002-02-17 Thread Carl R. Witty
Claus Reinke [EMAIL PROTECTED] writes: Haskell definitely supports abstraction and composition, so we can factor out application aspects (not just text) that need localisation, and link them (dynamically?) with the main parts of our applications. Some systematic approach would be useful,

Re: GHC Poll: scope in GHCi

2002-01-09 Thread Carl R. Witty
Simon Marlow [EMAIL PROTECTED] writes: Ok, so in general a 'scope' can be constructed by combining: 1. the full top-level scope from zero or more *interpreted* modules 2. the exports of zero or more modules (interpreted or compiled) 3. any temporary bindings made on the command

Re: ghc --make feature request

2001-10-26 Thread Carl R. Witty
Simon Marlow [EMAIL PROTECTED] writes: GHC actually has rather sophisticated recompilation checking which goes beyond just checking whether the interface changed - it keeps version information for each entity exported by a module and only recompiles if any of the entities actually used by

Re: rank 2-polymorphism and type checking

2001-10-24 Thread Carl R. Witty
Simon Peyton-Jones [EMAIL PROTECTED] writes: So I'm interested to know: if GHC allowed arbitrarily-ranked types, who would use them? I can't promise that I would use them, but it would certainly give me warm fuzzy feelings to know that they were there. :-) On the other hand, I believe that

Re: Monomorphism, monomorphism...

2001-10-10 Thread Carl R. Witty
Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED] writes: 09 Oct 2001 13:55:04 -0700, Carl R. Witty [EMAIL PROTECTED] pisze: The TREX paper from Mark Jones and Benedict Gaster (I hope I have the names right) had both extensible records and extensible variants (extensible variants being what

Re: HOpengl on Ghc 5.02

2001-10-09 Thread Carl R. Witty
Nicolas [EMAIL PROTECTED] writes: Hi there, Sorry for this stupid question: Is there a distrib of a HOpenGl package working with ghc 5.02. I tried the CVS but don't manage to make it work (ghc 5.03 panic). Can someone help me? I got HOpenGL to work without trouble. On September 29, I

Re: Monomorphism, monomorphism...

2001-10-09 Thread Carl R. Witty
Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED] writes: Since OO languages often use subtypes to emulate constructors of algebraic types, they need downcasts. In Haskell it's perhaps less needed but it's a pity that it's impossible to translate an OO scheme which makes use of downcasts into

Re: newtype | data

2001-10-05 Thread Carl R. Witty
Mark Carroll [EMAIL PROTECTED] writes: Why does newtype exist, instead of letting people always use data and still get maximum efficiency? After all, surely the implementation is an implementation detail - a compiler could see the use of data with a unary constructor and implement it as it

Re: Strange error in show for datatype

2001-10-03 Thread Carl R. Witty
Bjorn Lisper [EMAIL PROTECTED] writes: data LispList t = Atom t | LispList [LispList t] | Str [Char] instance Show t = Show (LispList t) where show (Atom t) = show t show (LispList t) = show t show (Str t) = show t hugsprompt (LispList [Atom 1, Str HEJ]) == [1,HEJ]

Re: RFC: GUI Library Task Force

2001-09-24 Thread Carl R. Witty
Manuel M. T. Chakravarty [EMAIL PROTECTED] writes: + More sophisticated approaches (that often require language extensions or are still experimental) can be implemented on top of this basic API - eg, FranTk, Yahu, Fruit, iHaskell, etc. I keep seeing references to Fruit

Re: unsafePtrCompare, anybody?

2001-09-17 Thread Carl R. Witty
Leon Smith [EMAIL PROTECTED] writes: However, in this situation, pointer comparison is simply an arbitrary total order on the set of all atoms, which is all we need to implement finite maps based on search trees. And of course, pointer comparisons are a much cheaper operation that actual

Re: GHC FFI Return Type Bug

2001-08-07 Thread Carl R. Witty
Sigbjorn Finne [EMAIL PROTECTED] writes: Julian Seward (Intl Vendor) [EMAIL PROTECTED] writes: Hmm, we're looking at this. However, I don't really know what C is or is not supposed to do here. Given char fooble ( ... ) { return 'z'; } on an x86, 'z' will be returned

Re: Why is there a space leak here?

2001-06-11 Thread Carl R. Witty
S. Alexander Jacobson [EMAIL PROTECTED] writes: On 6 Jun 2001, Carl R. Witty wrote: S. Alexander Jacobson [EMAIL PROTECTED] writes: For example w/ foldl: foldl + 0 [1..1] foldl (+) ((+) 0 1) [2..1] foldl (+) ((+) ((+) 0 1) 2) [3..1] Can't

Re: Why is there a space leak here?

2001-06-06 Thread Carl R. Witty
S. Alexander Jacobson [EMAIL PROTECTED] writes: For example w/ foldl: foldl + 0 [1..1] foldl (+) ((+) 0 1) [2..1] foldl (+) ((+) ((+) 0 1) 2) [3..1] Can't the implementation notice that each iteration leads to a larger closure and, if it is running out of space go ahead an

Re: Endangered I/O operations

2001-05-23 Thread Carl R. Witty
Simon Marlow [EMAIL PROTECTED] writes: You obtain the ordering properties by setting the handle to NoBuffering, otherwise you get buffered input/output. Wouldn't it be deviating from the report to do extra flushing in the buffered case? (this is something of a technicality, actually we

Re: Templates in FPL?

2001-05-22 Thread Carl R. Witty
D. Tweed [EMAIL PROTECTED] writes: In my experience the C++ idiom `you only pay for what you use' (== templates are essentially type-checked macros) and the fact most compilers are evolved from C compilers makes working with templates a real pain in practice. I'm not sure what you mean by

Re: Templates in FPL?

2001-05-22 Thread Carl R. Witty
Jerzy Karczmarczuk [EMAIL PROTECTED] writes: We know that a good part of top-down polymorphism (don't ask me what do I mean by that...) in C++ is emulated using templates. Always when somebody mentions templates in presence of a True Functionalist Sectarian, the reaction is What!?

Re: Happy and Macros (was Re: ANNOUNCE: Happy 1.10 released)

2001-05-14 Thread Carl R. Witty
Manuel M. T. Chakravarty [EMAIL PROTECTED] writes: I didn't say that this works for any kind of parser combinator, I merely said that it works Doitse's and mine. Both implement SLL(1) parsers for which - as I am sure, you know - there exists a decision procedure for testing ambiguity. More

Re: Happy and Macros (was Re: ANNOUNCE: Happy 1.10 released)

2001-05-14 Thread Carl R. Witty
Manuel M. T. Chakravarty [EMAIL PROTECTED] writes: I didn't say that this works for any kind of parser combinator, I merely said that it works Doitse's and mine. Both implement SLL(1) parsers for which - as I am sure, you know - there exists a decision procedure for testing ambiguity. More

Re: Happy and Macros (was Re: ANNOUNCE: Happy 1.10 released)

2001-05-11 Thread Carl R. Witty
Manuel M. T. Chakravarty [EMAIL PROTECTED] writes: I don't think, the point is the test for non-ambiguity. At least, Doitse's and my self-optimising parser combinator library will detect that a grammar is ambigious when you parse a sentence involving the ambiguous productions. So, you can

Re: Happy and Macros (was Re: ANNOUNCE: Happy 1.10 released)

2001-05-11 Thread Carl R. Witty
Manuel M. T. Chakravarty [EMAIL PROTECTED] writes: I don't think, the point is the test for non-ambiguity. At least, Doitse's and my self-optimising parser combinator library will detect that a grammar is ambigious when you parse a sentence involving the ambiguous productions. So, you can

Re: Happy and Macros (was Re: ANNOUNCE: Happy 1.10 released)

2001-05-10 Thread Carl R. Witty
S. Alexander Jacobson [EMAIL PROTECTED] writes: I am not a parsing expert, but given the recent discussion on macros, I have to ask: why use happy rather than monadic parsing? Monadic parsing allows you to avoid a whole additional language/compilation step and work in Hugs (where you don't

Re: type class

2000-10-02 Thread Carl R. Witty
Simon Peyton-Jones [EMAIL PROTECTED] writes: | How about extending TC with a branch for abstraction: | | TC ::= ... | | /\a. TC -- abstraction | | This is too powerful and will get out of control -- we surely | don't want to give TC the full power of lambda-calculus. So let's

Re: How to force evaluation entirely?

2000-09-26 Thread Carl R. Witty
John Hughes [EMAIL PROTECTED] writes: As far as the power of the optimizer is concerned, my guess is programmers very rarely write x==x (unless they MEAN to force x!), so the loss of optimization doesn't matter. Of course, in principle, an optimizer *could* replace x==x by x`seq`True (if x

Re: Extensible data types?

2000-09-25 Thread Carl R. Witty
Jose Romildo Malaquias [EMAIL PROTECTED] writes: Hello. Is there any Haskell implementation that supports extensible data types, in which new value constructors can be added to a previously declared data type, like data Fn = Sum | Pro | Pow ... extend data Fn = Sin

Re: monadic source of randomness

2000-08-09 Thread Carl R. Witty
Norman Ramsey [EMAIL PROTECTED] writes: Does anybody know of work using monads to encapsulate a source of random numbers? A quick web search suggested Haskell 98 did not take this path. I'd be curious for any insights why, or any suggestions about a `randomness monad'. My guess as to why

Re: Classes

2000-08-03 Thread Carl R. Witty
[EMAIL PROTECTED] (Carl R. Witty) writes: "Claus Reinke" [EMAIL PROTECTED] writes: Fergus (and others): how about compiling a summary of the relationships (a kind of dictionary of terminologies) ? In particular, what is the state of the art in logic programming wrt d

Re: Classes

2000-07-31 Thread Carl R. Witty
"Claus Reinke" [EMAIL PROTECTED] writes: Fergus (and others): how about compiling a summary of the relationships (a kind of dictionary of terminologies) ? In particular, what is the state of the art in logic programming wrt determinism and termination analysis? Can you recommend any

Re: Precision problem

2000-07-18 Thread Carl R. Witty
Fergus Henderson [EMAIL PROTECTED] writes: Yes, but for any given Haskell program execution, the sum of any two floating-point values should be the same every time you compute it. In general it need not be the same as the sum of the equivalent real numbers, because floating point numbers are

Re: mode in functions

2000-06-01 Thread Carl R. Witty
Simon Raahauge DeSantis [EMAIL PROTECTED] writes: It seems to me that mode flags only really make sense when we're combining modes. To continue the tar example it might be a bit much to have extractVerbosePreserve, extractPreserve etc etc. This is also done in C by |'ing 'flags' together for

bug in ghc, hugs, or green-card

2000-05-31 Thread Carl R. Witty
As you can tell from the title, I'm not sure exactly where the responsibility for this bug lies. The symptom: green-card (running under hugs, with runhugs) fails when running in a project directory built with "ghc -split-objs". The cause: Green Card does import chasing; that is, when processing

typo in CVS users_guide/4-07-notes.sgml

2000-05-30 Thread Carl R. Witty
The file 4-07-notes.sgml in the latest CVS mentions http://www.cse.ogi.ed/~jlewis/implicit.ps.gz That should be .edu, not .ed . Carl Witty [EMAIL PROTECTED]

typo in CVS hslibs/lang/doc/IArray.sgml

2000-05-30 Thread Carl R. Witty
The file IArray.sgml in the latest CVS says "additiona" instead of "addition". Carl Witty [EMAIL PROTECTED]

Re: Fw: more detailed explanation about forall in Haskell

2000-05-16 Thread Carl R. Witty
"Jan Brosius" [EMAIL PROTECTED] writes: SORRY, this is quite TRUE , in fact [forall x. alpha(x)] = alpha(x) the above true equivalence seems to be easily considered as wrong . Why? Because alpha(x) is TRUE can be read as alpha(x) is TRUE for ANY x. (Is there something wrong with

Re: speed and size of compiled Haskell code

2000-03-17 Thread Carl R. Witty
Fergus Henderson [EMAIL PROTECTED] writes: On 16-Mar-2000, Jan Brosius [EMAIL PROTECTED] wrote: I wonder if someone could tell me more about the speed and size of compiled Haskell code. ... What about Haskell 98 versus (I anticipate) Haskell 2 There should be no significant

Re: overlapping instances

2000-02-07 Thread Carl R. Witty
"Jeffrey R. Lewis" [EMAIL PROTECTED] writes: Marcin 'Qrczak' Kowalczyk wrote: Parts of context reduction must be deferred, contexts must be left more complex, which as I understand leads to worse code - only to make overlapping instances behave consistently, even where they are not

Re: A Haskell-Shell

1999-08-23 Thread Carl R. Witty
Heribert Schuetz [EMAIL PROTECTED] writes: Hi, The appended patch to Hugs98 (to be applied in the src subdirectory) might be of some help for those who want to do shell scripting in Haskell. It modifies IO.openFile as follows: - If the name of a file opened in ReadMode ends in "|", then

Re: Stylistic question about Haskell optional arguments

1999-08-18 Thread Carl R. Witty
Paul Hudak [EMAIL PROTECTED] writes: Carl I'm afraid this doesn't work. There are two problems: Carl 1) You need a constructor above: h1 (stringToHtml "This is a Header" (H1Args { align = Right})) Carl or H1 { align = Right, html = stringToHtml "This is a Header" } and Marko

Re: Stylistic question about Haskell optional arguments

1999-08-17 Thread Carl R. Witty
Paul Hudak [EMAIL PROTECTED] writes: One alternative is to use labelled fields. In your example, if Html were an algebraic datatype such as: data Html = Type1 { align = Align, ... } | Type2 { align = Align, ... } | ... data Align = Left | Right | Center then

Re: diagonalization

1999-07-20 Thread Carl R. Witty
Hans Aberg [EMAIL PROTECTED] writes: This is in fact one of the more easy questions: One defines a list l on a set A to be a map l: [0, x) - A on a semi-open interval [0, x), where x is an ordinal, and 0 is the first (smallest) ordinal. Then the set of all lists have type list ([A] in

Re: diagonalization

1999-07-19 Thread Carl R. Witty
Hans Aberg [EMAIL PROTECTED] writes: I think that the original problem is due to the fact that Haskell does not know how to handle ordinals properly: Let S be the set of countable finite ordinals; if w = \omega is the first countably infinite ordinal and N the set of natural numbers, then

tiny bug in docs/libraries/Weak.sgml

1999-05-05 Thread Carl R. Witty
Whoever did the global search-and-replace of "finalise" by "finalize" missed the word form "finalisation". Carl Witty [EMAIL PROTECTED]

Re: Haskell 2 -- Dependent types?

1999-02-28 Thread Carl R. Witty
Lennart Augustsson [EMAIL PROTECTED] writes: (I believe that there are type theories with dependent types, such as the one in Thompson's _Type Theory and Functional Programming_, where each term has at most one type; so it can't just be dependent types that disallow principal types.)

Re: Haskell 2 -- Dependent types?

1999-02-28 Thread Carl R. Witty
Fergus Henderson [EMAIL PROTECTED] writes: Could you give an example of language syntax that you feel would be better than putting these properties in the type system, while still allowing similar compile-time checking? I already gave NU-Prolog and Eiffel as examples. Those languages

Re: Haskell 2 -- Dependent types?

1999-02-25 Thread Carl R. Witty
Nick Kallen [EMAIL PROTECTED] writes: You cannot do this in Cayenne, there are no operations that scrutinize types. They can only be built, and never examined or taken apart. This is a deliberate design choice. The consequence is that type cannot affect the control of a program, so

Re: Haskell 2 -- Dependent types?

1999-02-25 Thread Carl R. Witty
Fergus Henderson [EMAIL PROTECTED] writes: Certainly a language with dependent types should define exactly what types the type checker will infer. But when generating code, the compiler ought to be able to make use of more accurate type information, if it has that information available,

Re: Haskell 2 -- Dependent types?

1999-02-25 Thread Carl R. Witty
[Resend - mlist trouble; apologies if you've already received it. -moderator] Lennart Augustsson [EMAIL PROTECTED] writes: 2) Yes, I agree that the possibility that user-supplied type declarations can change the meaning of the program is a strike against the idea. I don't find that so

Re: Haskell 2 -- Dependent types?

1999-02-25 Thread Carl R. Witty
"Nick Kallen" [EMAIL PROTECTED] writes: If this is true, then what I'm doing is horrible. But I don't see how this leads to nondeterminism or broken referential transparency. min2 returns the same value for the same list, but it's simply more efficient if we happen to know

Re: Haskell 2 -- Dependent types?

1999-02-24 Thread Carl R. Witty
[EMAIL PROTECTED] writes: [EMAIL PROTECTED] writes: enabling types to express all properties you want is, IMO, the right way. Why do I feel that there must be another approach to programming? How many people do you expect to program in Haskell once you are done adding all it takes to

Re: Haskell 2 -- Dependent types?

1999-02-16 Thread Carl R. Witty
Lars Lundgren [EMAIL PROTECTED] writes: We have already accepted undecidable type checking, so why not take a big step forward, and gain expressive power of a new magnitude, by extending the type system to allow dependent types. Wait a minute...who has accepted undecidable type checking?

Re: syntactic sugar for arrows

1999-01-29 Thread Carl R. Witty
Ross Paterson [EMAIL PROTECTED] writes: Time to ditch all those dusty old monads and upgrade to arrows. However the point-free style of that paper won't appeal to everyone. I've placed a proposal for a Haskell extension with a do-notation-style syntax for arrows at

Re: kind mismatch ($)

1999-01-04 Thread Carl R. Witty
Simon Peyton-Jones [EMAIL PROTECTED] writes: One additional comment. I frequently use quotes (') as suffixes for identifier and type names. As can be seen above ghc loves adding quotes (` and ') around parts of its messages. This becomes *very* confusing when the last part of the message

Re: Reduction count as efficiency measure?

1998-11-25 Thread Carl R. Witty
Keith Wansbrough [EMAIL PROTECTED] writes: So while Hugs gives you a reduction count (or even a millisecond duration), this is essentially meaningless: in a real application you would compile the code with an optimising compiler. The effect this can have on your execution time can easily be

Re: Reduction count as efficiency measure?

1998-11-25 Thread Carl R. Witty
Ralf Hinze [EMAIL PROTECTED] writes: | Is this true in practice? That is, are there programs which have | different asymptotic running times when compiled under ghc or hbc than | when running under Hugs? | | It would actually surprise me if there were; I'm having a hard time | imagining

Re: Int vs Integer

1998-09-11 Thread Carl R. Witty
Sigbjorn Finne [EMAIL PROTECTED] writes: This wants to add two 1-word numbers in a fast, unrolled loop. It sets up various registers (size, and pointers to source1, source2, and destination). It computes the number of complete times to go through the

Re: ghc-2.10 fails on Red Hat Linux 5.0?

1998-05-27 Thread Carl R. Witty
Antony Bowers [EMAIL PROTECTED] writes: Does ghc (any version) work on Linux with glibc-2 (libc6)? It works for me. I installed the 2.10 binary release and used it to compile 3.01 from source; both 2.10 (which is linked with libc5) and 3.01 (which is linked with libc6) can compile the

problems compiling ghc 3.01 for linux

1998-05-11 Thread Carl R. Witty
I ran into minor problems compiling GHC 3.01 on my up-to-date Debian Linux machine. I'm pretty sure that the problem is that I'm using Libc 6 (GNU libc 2). Basically, several BSD extensions (in particular, the types caddr_t and u_long, and the tm_zone and tm_gmtoff members of struct tm) are not

Re: problems compiling ghc 3.01 for linux

1998-05-11 Thread Carl R. Witty
Simon Marlow [EMAIL PROTECTED] writes: Thanks Carl. Several people have run into this before (check the list archives), but we still don't have any recent Linux installations here to test out a proper fix on. That's why I said: Let me know if you have any questions, or want me to test

Re: quicksort and compiler optimization

1998-05-10 Thread Carl R. Witty
Mariano Suarez Alvarez [EMAIL PROTECTED] writes: qsort can be rewritten (by the compiler, ideally...) so that the list is traverse once, without losing any laziness: infix 5 # infix 6 ?: Define qsort [] = [] qsort (x:xs) = let (a,b) = foldr (\y - (y ?: (x) # y ?: (=x)))

Re: Is this a bug?

1998-03-06 Thread Carl R. Witty
Marc van Dongen= [EMAIL PROTECTED] writes: [snip] : module Main( main ) where : import List( genericLength ) : main = putStr (show integral) : putStr "\n" : return () :where integral = genericLength [] [snip] : This is a legal Haskell

Haskell 1.4 and Unicode

1997-11-07 Thread Carl R. Witty
I have some questions regarding Haskell 1.4 and Unicode. My source materials for these questions are "The Haskell 1.4 Report" and the files ftp://ftp.unicode.org/Public/2.0-Update/ReadMe-2.0.14.txt and ftp://ftp.unicode.org/Public/2.0-Update/UnicodeData-2.0.14.txt It's possible that

small wart in the Report's description of the layout rule

1997-11-07 Thread Carl R. Witty
The Haskell Report says: To facilitate the use of layout at the top level of a module (an implementation may allow several modules may reside in one file), the keyword module and the end-of-file token are assumed to occur in column 0 (whereas normally the first column is 1). Otherwise, all

printing the ghc source?

1997-10-01 Thread Carl R. Witty
I'm interested in learning how GHC works. To this end, I'd like to print out large chunks of its source and pore over them. I would have hoped that the fact that GHC is written in the "literate programming" style would make it easy to get high-quality printouts; however, it doesn't seem to