Importing in a .hi-boot file

1999-07-08 Thread Keith Wansbrough
Hi... if I write a .hi-boot(-5) file that imports from another module (in this case to re-export), GHC looks for that module's .hi file. I would prefer it to look for a .hi-boot file. __interface TypeFr 1 0 where __export TypeFr Type Kind SuperKind ; 1 data Type ; 1 type Kind = Type ; 1 type

RE: Non-exhaustive pattern

1999-07-08 Thread Simon Peyton-Jones
Quite right. A glitch from the new parser. I'll fix it today. Thanks for the report Simon -Original Message- From: [EMAIL PROTECTED] Sent: Wednesday, July 07, 1999 8:08 PM To: GHC Bugs list Subject: Non-exhaustive pattern Hi! \begin{code} f = _ \end{code} yields:

RE: rules

1999-07-08 Thread Simon Peyton-Jones
You need to write the function in prefix form, thus: {-# RULES "T" forall x. (||) True x = True #-} I know this is stupid, but I havn't got around to fixing it. Simon -Original Message- From: [EMAIL PROTECTED] Sent: Thursday, July 08, 1999 2:46 PM To: [EMAIL PROTECTED]

cvs update hdirect fails

1999-07-08 Thread George Russell
When I try to do cvs update hdirect from the anonymous repository, it fail: cvs [server aborted]: cannot open directory /cvs/fptools/hdirect/tests/PRIVATE: No such file or directory

Re: Rule question.

1999-07-08 Thread Kevin Atkinson
Simon Peyton-Jones wrote: Sorry it's taken me a long time to look at this. Two things are going on here. No problem module KevinB where data Arr ix el = Arr Int [(ix,el)] deriving Show replaceMany :: [(ix,el)] - Arr ix el - Arr ix el replaceMany = error "In Replace Many"

RE: Rule question.

1999-07-08 Thread Simon Peyton-Jones
Kevin Sorry it's taken me a long time to look at this. Two things are going on here. First thing module KevinB where data Arr ix el = Arr Int [(ix,el)] deriving Show replaceMany :: [(ix,el)] - Arr ix el - Arr ix el replaceMany = error "In Replace Many" {-# RULES

RE: Calling Haskell from C

1999-07-08 Thread Simon Marlow
But before you do that do a gdb -c core in the directory ghc/lib/std/ to figure out what is really crashing. My unlit might of been crashing because I had the header files for glibc2.0 but the binaries for glibc2.1 installed. It could make a bit of a difference ;) True - I thought it

In-place update

1999-07-08 Thread Keith Wansbrough
Doesn't haskell 98 allow in place updating e.g; for records? [see next message] I have read this message and now I have the following question: Does this mean that a compiled program written in a strict functional language will be faster than the "same" program compiled with

RE: second rank polymorphism

1999-07-08 Thread Frank A. Christoph
Let me take a shot at this. Jan Brosius writes: Now I have some difficulty to follow. If I write id :: a - a then I thought it meant " id is a "function" from type a to type a " ; in logic this is completely equivalent with (since a is a variable ): " forall a ( id is a function from

RE: second rank polymorphism

1999-07-08 Thread Frank A. Christoph
I wrote: For example, we know just from the fact that concat : Forall a. a - a, that \xs.map A B f (concat A xs) = \xs. concat B (map A B f xs) where map : forall a. forall b. A - B - ([A] - [B]). Here the endofunctor in question is the list functor, []. Oops, I really screwed this up.

deriving Enum. Reply

1999-07-08 Thread S.D.Mechveliani
Keith Wansbrough [EMAIL PROTECTED] wrote on July 8 I find this a little surprising. In general, any algebraic datatype satisfying the conditions in Appendix D of the report should be enumerable, using the same lexicographic ordering used in D.1 for Eq and Ord. [..] Any problems with

Re: Random Access Files in Haskell

1999-07-08 Thread Sven Panne
Damir Medak wrote: Any experiences or hints how to implement Random Access Files in Haskell? Nhc's Binary lib is a little overkill for random access (though it's quite nice for other stuff :-). In vanilla Haskell you can simply use hSeek/hGetPosn/hSetPosn, see

re: Random Access Files in Haskell

1999-07-08 Thread Colin . Runciman
A little while ago Damir Medak asked: | Any experiences or hints how to implement Random Access Files | in Haskell? The Binary library distributed with nhc13 and nhc98 supports random access. It can be used to implement indexed file structures of various kinds. See

Re: Deriving Enum

1999-07-08 Thread Keith Wansbrough
I find this a little surprising. In general, any algebraic datatype satisfying the conditions in Appendix D of the report should be enumerable, using the same lexicographic ordering used in D.1 for Eq and Ord. [..] Any problems with this? I've seen one problem in my proposal. It's fine

TCP/IP Implementation for Haskell

1999-07-08 Thread Tamara Rezk
Do anyone know where can I get any implementation of TCP/IP for haskell? Thanks. Tamara Rezk

RE: Deriving Enum

1999-07-08 Thread Fermin Reig Galilea
I find this a little surprising. In general, any algebraic datatype satisfying the conditions in Appendix D of the report should be enumerable, using the same lexicographic ordering used in D.1 for Eq and Ord. [..] Any problems with this? I've seen one problem in my

Re: deriving Enum. Reply

1999-07-08 Thread Keith Wansbrough
And for other constructor kind, like say, Pair, List ... "deriving" does not seem to make much sense. Because there exist too many equally good ways to `enum' these types. Hence, it is better to leave this for the possible separate user Enum declaration. Ah, but the same is true for Ord

re: virtual terminal in Haskell

1999-07-08 Thread Colin . Runciman
Marcin Kowalczyk (I think) wrote: | I have to think about a good abstraction of terminal actions. I don't | quite like ... because it does not allow integration with arbitrary IO | (or I miss something?) and it heavily depends on the terminal having | particular properties, offered in a