Local definitions in the class instances

Iavor Diatchki iavor.diatchki at gmail.com
Thu Jan 27 18:11:15 CET 2011


Hello,

One issue I can see with such a change is that now it is not obvious which
declarations define methods in the instance, and which are just helper
functions.  For example, currently, if I mistype the name of a method in a
class (which happens often), the program is rejected because there is no
such method in the class.  With this change, the program would be accepted
because the method would be "undefined" and the mistyped implementation
would be considered as just another local declaration.

I have also encountered the underlying problem that you describe---wanting
more control over the scoping of declarations.  Perhaps we should extend
Haskell with something like ML's "local" declarations: local D1 in D2.  Such
a declaration defines what D2 defines, but the implementations in D2 may use
the names defined in D1 (i.e., it is like a "let" which scopes over
declarations rather then expressions).   This would help with your problem:

instance Num Wrapped where
   local
     lift2 f (Wrapped a) (Wrapped b) = Wrapped (f a b)
     lift f (Wrapped a) = Wrapped (f a)
   in
    (+) = lift2 (+)
    (-) = lift2 (-)
    (*) = lift2 (*)
    abs = lift abs
    signum = lift signum

It would also be useful in other situations.  For example, currently if we
have a module which exports most of its functions but not all, we have to
write a long export list.  This could be avoided with a local declaration:

module M where

local
  not exported functions
in
  exported functions

Of course, one could also scope the private functions more precisely.  I am
not sure what would be good syntax for a concrete proposal but I think that
this is a nice construct to have.

-Iavor





On Thu, Jan 27, 2011 at 3:07 AM, Boris Lykah <lykahb at gmail.com> wrote:

> I think it would be convenient to allow adding variables and
> functions, which are not members of the class,  to a class instance so
> that they are visible only in the instance scope. It will help if the
> same functions are used by several class functions.
>
> Example:
> When implementing Num class for my datatype, I found that I routinely
> do unwrapping in each operator definition. I extracted it into
> functions, but as they are used only in instance definition, I want to
> put them there and restrict them to that scope. It would be neater
> than leaving them in the global scope or copypasting into each
> operator.
>
> > newtype Wrapped = Wrapped Integer deriving (Show, Eq)
>
> > instance Num Wrapped where
> >   (+) = lift2 (+)
> >   (-) = lift2 (-)
> >   (*) = lift2 (*)
> >   abs = lift abs
> >   signum = lift signum
> >   fromInteger = Wrapped
> >   lift2 f (Wrapped a) (Wrapped b) = Wrapped (f a b)
> >   lift f (Wrapped a) = Wrapped (f a)
>
> The extension implementation should be very simple.
>
> --
> Regards,
> Boris
>
> _______________________________________________
> Haskell-prime mailing list
> Haskell-prime at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-prime
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-prime/attachments/20110127/d1266eea/attachment.htm>


More information about the Haskell-prime mailing list