type aliases in instances

Jay Cox sqrtofone@yahoo.com
Mon, 11 Mar 2002 22:35:47 -0600 (CST)


On Mon, 11 Mar 2002, Bernhard Reus wrote:

> Richard Uhtenwoldt wrote:
> >
> > I do not have experience commposing monads (maybe John Hughes can
> > chime in?), but I'll address where Bernhard Reus writes:
> >
> > >This can be avoided by using type
> > >aliases but then the monads in use cannot be instances of the Monad
> > >class.
> > >But not declaring the monads to be in class Monad can hardly
> > >be good style, can it?
> >
> > GHC's source code defines many monads not in class Monad.
> > I'll write some untested code to give an idea of
> > the naming conventions used:
> >
> > type FooMd out = (a,b,c)->((a,b,c),out)
> > returnFooMd out = \s0->out
> > thenFooMd p k = \s0->let (s,out) = p s0
> >
>
> Thanks Richard. So this means it is common practice in the Haskell
> community to use type aliases and not to declare the monads as
> instances.

I don't know about that.  Andy Gill has a a monad library out there
(sorry, the link I have is not in use anymore) that basically uses the
newtype psuedo-type aliases. If I needed to construct monad for myself, I
certainly wouldn't use "type".  I'm sure most others feel the same way.

Besides, there might be any number of reasons that GHC could use type
aliases.  The first that comes to mind is the old rule, "If it works,
don't fix it."  As I haven't read the sourcecode, I can only guess.

> But that makes me even more curious. Why are type aliases not allowed in
> instance declarations? I haven't found an explanation in the language
> doc. Does anybody know the exact reason?   Any pointer appreciated.

With glasgow extensions, (perhaps hugs has this extension too?) you could
use almost any arbitrary type.  But as SPJ said in a previous post, you
cannot have standalone "curried" type alias expressions, therefore I
believe you, shouldn't be able to use type aliases for a definition of a
Monad or Functor instance.  (Hey, I tried! the original message
that inspired this thread inspired me to do so.)

As an example, I created this half finished library which allows one to
type non-polymorphic expressions with type-classes.  It uses ghc's
-fallow-overlapping-instances so that something of type, say, String ->
[(a,String)] as a "Parser a" (The "Parser a" example not included in
source code).  It also uses glasgow-exts, but I believe its only need is
to express the type of the constant bottomless, which because it is
polymorphic, I use to assign types to multiple instances of it.
(basically, I have built a type class that recurses down the type
expression trees.) and, well, perhaps another extension.  I'm to lazy to
research the names of all extensions :).  The code is suprisingly trivial,
if one can understand it.

Here's a tidbit from the library

>bottomless:: forall a. a
>bottomless=error "This shouldn't happen in the HasType Module"
>
>class HasType a where
>  istype :: a -> String

<snip>

>instance HasType a => HasType(IO a) where
>  istype _ = "IO (" ++ istype (bottomless::a) ++ ")"

If you want to take a look at more of it goto

http://www.flash.net/~flygal/Jay/Haskell/HasType.lhs

sometime.  by that time you get it, it may look alittle different, as i
perfect it, change it so that it doesn have to outragous runtime, change
the class definition, actually define it as a Module, or whatever.

Again, this is a temporary place, until I find a more permanent place,
(like my own domain name.)

I've digressed.

Back to the problem of using type aliases, A problem with using
overlapping instances is that you might want to use instances which
overlap equally.  For example, what if I wanted to use some alias for
an arbitrary tuple?  The type checker cannot tell the difference between
the aliased type and the other, which means you cannot make the two
instances

type Alias1 =Type1

instance Foo Type1 where
  ...

instance Foo Alias1 where
  ...


Which you dearly might if you wanted to interpet your conception of
what your type alias "means" into your program.

That's probably why newtype was invented.


Jay Cox