> 1.
> Haskell-98 description
> - is it ready to print as the final, accepted and approved document?

Design frozen: but I'm working right now on the actual final document.

>   class Num' a where  add,sub :: a -> a -> a
>                       neg     :: a -> a
>                       sub x y = add x (neg y)
> 
> What might be the cost overhead (depending on implementation!),
> if we move  sub  to separate polymorphic function:
> 
>   sub :: Num' a => a -> a -> a
>   sub x y = add x (neg y)

In GHC the efficiency differences either way are pretty slight. 
I think.

> Module export:
> if a module  N  has to export only a couple of instances for the 
> constructor defined in  M,  how does it say that nothing else is for
> export?
> Thus, in the following example, one has to hide 
>                                              localThing1, localThing2:
>   module M ( C(..), ... )
>   where
>   data C a = ...
>   -------------------
>   module N ( ?? )
>   where
>   import M (C(..))
>   instance ...=> I1 (C a) where  c x = localThing1 x
>   instance ...=> I2 (C a) ...
> 
>   localThing1 = ...
>   localThing2 = ...
> 
> 
> Probably,  module N (C(..))  will do. Have we really to re-export C ?

So the idea is *all* N does is to define instances?  The H98 report
Section 5.4 says that if you import a module you get all the instances
in it.  Period.  So N doesn't need to export anything:

        module N() where
          import M
          instance ...
          instance ...

        module Client where
          import N      -- You get N's instances and nothing else

Simon



Reply via email to