PrelTup

1998-04-20 Thread Manuel Chakravarty

Hi Glaswegians,

[This is not necessarily a bug; nevertheless, any advice
would be appreciated.]

During linking of a (big) Happy generate file, I ended up
with a linker message like

KCParser.o(.text+0x41a9f): undefined reference to 
`PrelTup_Z40Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z41_con_info'

This is GHC 2.05 and Happy 1.2-alpha on a Linux box
(installed from source).

Could this message arise when I use a tuple with too many
components or something like this?  (Sorry for such an
unprecise report, but trying to reduce this to a small file
isolating the problem would be quite some work; so, I want
to check whether it is some simple problem first.)

Thanks for any help,

Manuel



Re: Confusing error message

1998-02-18 Thread Manuel Chakravarty

  I encountered a confusing error message, which you can
  reproduce with 
  
type P a = Maybe a
  
instance Monad P where
  (=)  = error "foo"
  return = error "bar"
  
  I get 
  
bug.hs:5: `P' should have 1 argument, but has been given 0 .
 
 Would it be better if it said 
 
   Type synonym constructor P should have 1 argument,
   but has been given 0
 
 Haskell requires that type synonyms are never partially applied;
 that's what's being complained about here.
 
 If you did fully apply it, GHC 3.1 (without -fglasow-exts) would
 then complain about making an instance of a type synonym.
 At the moment, though, it trips over the mal-formed type expression first.

That's what I guessed, but I reckon that it may be a bit
difficult to spot for people who are not so familiar with
the details of constructor classes.  But, maybe it is too
much fuzz to check for this special situation explicitly.

I wonder whether it would be helpful to add a comment like

  (or if this is a instance declaration, type synonyms are
  not allowed)

to the message.

Manuel



Confusing error message

1998-02-17 Thread Manuel Chakravarty

Hi GHC-Developers!

I encountered a confusing error message, which you can
reproduce with 

  type P a = Maybe a

  instance Monad P where
(=)  = error "foo"
return = error "bar"

I get 

  bug.hs:5: `P' should have 1 argument, but has been given 0 .

with 

  ** ghc 2.05 **

(maybe things changed in the meanwhile.)

The problem in the program is clear, we cannot have an
instance of a type synonym, but that's far from obvious from
the error message.

Cheers,

Manuel




Floats don't like to be referenced [was: Buggy derived instance of Show]

1998-01-29 Thread Manuel Chakravarty

Scary, but true...the floats in my version of ghc don't like 
to be referenced.  The program

  data MassPnt  = MassPnt Float (Float, Float)
  deriving (Show)

  main = do
   print 1.18088e+11-- (1)
   let 
 x = 1.18088e+11
 p = MassPnt x (-0.768153, -0.742202)   -- (*)
   print x  -- (2)

prints `1.18088e+11' successfully at line (1), but fails in
line (2) with `Fail: Char.intToDigit: not a digit'.

But now the *interesting* part: When I remove the line (*),
everything works just fine!  Floats just don't like to be
referenced...or is there not enough space allocated for them
in the heap and they tend to be overwritten?

Now, I don't have the lattest version of GHC, so maybe
someone else hit that problem earlier (I also did't follow
all discussions on this list).  (As said earlier, I used ghc
2.05 on Linux 2.0.30.) 

Manuel

P.S.: Of course, I think that the problem that I reported
  earlier was actually caused by the above one.




Re: ghc Diagnostics

1997-10-14 Thread Manuel Chakravarty

Simon Marlow wrote:

 I take your point that this isn't very consistent:  there should be a
 way to turn off all warnings easily.  What do other people think?
 
 The options are:
 
   * have all warnings off by default, a standard set of warnings
 being available by adding the -W command line option.
 
   * have a standard set of warnings on by default, with all
 warnings being turned off by the -Wnot (or something) flag.

I'd prefer to have the warnings off by default.  And why
don't go for a command line option set like that of the
`gcc'?  Then, `-Wall' activates all warnings and you can
get the individual warnings with `-Wwarning name'.

Manuel




Re: GHC status

1997-07-24 Thread Manuel Chakravarty

 I read a nice paper recently "The cathedral and the bazaar" by Eric Raymond,
 reflecting on his experience Linux, and in particular of developing
 "fetchmail".  You can find it at
   http://locke.ccil.org/~esr/writings/cathedral.html
 
 It's really worth reading.  One particular thing he suggests is making very
 frequent releases, even if they are buggy (like daily when in intense
 development mode).  I've been brought up to think that releasing buggy
 software is likely to discourage one's users, but perhaps not if the
 non-buggy versions (ha!) are prominently so flagged, so that "users" can
 stick to them, while "developers" can pull in the latest one.  Comments? 
 (Read the Raymond paper first.)

Very nice paper, I greatly enjoyed reading it. I think that the Linux
kind of frequent releases may actually be worth a try. For the
libraries it is most certainly worth it. For the compiler proper, it
probably depends heavily on how many people actually install the
sources or even build from them. My impression from the mailing lists
is that a substantial number of users do this.

Probably a version numbering scheme like that of Linux is necessary to
distinguish stable from experimental versions (Linux uses X.Y.Z where
Y is even for stable and odd for experimental versions). Linux ftp
sites usually keep the even and odd kernel versions in two separate
subdirectories to avoid confusion.

Manuel



Re: A new view of guards

1997-04-29 Thread Manuel Chakravarty

 I would really welcome feedback on this proposal.  Have you encountered
 situations in which pattern guards would be useful?  Can you think of ways
 in which they might be harmful, or in which their semantics is non-obvious?
 Are there ways in which the proposal could be improved?  And so on.

On first reading, I don't have any suggestions, but I fully agree that
the mentioned clunky function definitions are a nuisance and occur
often. The proposed syntax may look a bit strange in the beginning,
but I find the upward compatibility and the simple changes to the
grammar very attractive.

Manuel






fixpoint combinator in monads

1996-07-22 Thread Manuel Chakravarty

Hi!

For monads like the `IO' monad, is there any reason for not providing
a monad operator wrapping the fixpoint combinator into the monad? I
mean a function

  fixM :: (a - M a) - M a

for some monad `M', which feeds its argument the result eventually
produced by the overall monadic computation. So, something like

  fixM (\x - unitM (1:x)) 

provides the same *cyclic* data structure (within the monad) as would

  unitM (let x = 1:x in x)

Actually, such an operator is provided in GHC's libraries for `ST' and
`PrimIO' (called `fixST' and `fixPrimIO' -- defined in the modules
`PreludeGlaST' and `PreludePrimIO'), but it is not defined for `IO' in
Haskell 1.3.

Sometimes such an operator can be useful -- I just wanted to use it
-- and it is impossible to define the thing for yourself (if you don't
have access to the internals of the monad). Are there any good reasons
not to add it to `IO'?

With regard to adding the thing to the monad classes of Haskell 1.3, I
think that is probably be too much fuss. The operation can probably
not be defined for some monads -- (a) otherwise, the monad laws
wouldn't be complete and (b) I don't know a sensible way to define it
for the list monad. But there are monads in `MonadZero' and
`MonadPlus' which allow such a fixpoint operation, namely `Maybe'.

Any opinions?

Cheers,

Manuel





Haskell 1.3: modules module categories

1995-09-30 Thread Manuel Chakravarty


Hi!

Talking to a friend, who is project manager in a software company, about
modules for Haskell, he made two comments that may be of interest to the
current discussion.

(1) With regard to the idea of 99% hand-written interfaces (just mark everthing
that should go into the interface in a combined interface/implementation
file) that I proposed and that was supported by Peter, my friend pointed
out that this could make multiple implementations for one interface a bit
more labour. You basically have to guarantee that the interfaces extracted
out of the combined file for version one and version two of the
implementation are equal, i.e., the interface is duplicated in both
versions.

Still, I find this less onerous than having a separate implementation and
interface for three reasons: (1) the common case is one implementation for
one interface (better shift the labour to the occasional case); (2) in the
Modula-2 style there is also some duplication of code (procedure/function
signatures); and (3) in the case of two implementations for one interface
you have to deal with issues of consistency between the versions anyway.

(2) He pointed out that it is desirable to be able to restrict the access to
some modules in a way that the compiler can control when a group of people
is working in one module hierarchy. Too illustrate this, assume that we
classify the modules into different levels of abstraction, say, three
levels: 

  level 3 modules

|
v

  level 2 modules

|
v

  level 1 modules

Now the modules in level 2 may use the modules from level 1; the modules
from level 3 may use the modules from level 2, but *not* the modules from
level 1---I think it is clear that such a case is rather frequent. Such
access control may be easy to achieve when it is possible to deny the
people working on level 3 the access to the interfaces of level 1 (e.g.,
don't copy them the interface or use UNIX file permissions). But this may
often not be possible, for instance because some people are working at
modules in level 2 and 3. So, we like to have some way to specify that the
compiler simply does not allow to import (directly) modules from level 1
within modules from level 3.

Actually, C++ has a rather ad-hoc solution (are you suprised?) to this
problem, the `friends'. An object may be friend of another object; then,
that object can access (private) fields that are not visible to other
non-friend objects. The problem here is that the object providing some
service has to specify all its friends, by name. If it is required to add a
new friend, the used object has to be changed. Consider, in our example
hierarchy, that you want to split some existing level 2 module into two
modules; using friends, this requires to change modules in level 1, which
is obviously bad.

Now, what about the following idea? Each module is element of a module
category. Such categories are named and each module states to which
category it belongs. Furthermore, a module lists all categories of which
the members may import it. In the example, we have three categories, say,
Level1, Level2, and Level3. All modules from Level1 allow to be imported
from Level2, and all modules from Level2 allow to be imported from
Level3. This pervents imports of modules of category Level1 from modules in
category Level3, and is easy to check for the compiler. Splitting a module
does not require any changes in underlying categories.

Cheers,

Manuel