[Haskell] Type Class Question
Paul Govereau
govereau at eecs.harvard.edu
Tue Nov 22 02:56:27 EST 2005
Ah yes, but this forces me to write my instance of Show right away. I
cannot write:
module A where data X = X
module B where
import A
bar x = show x -- here is the problem
moduel C where
import A
instance Show X where show x = "X"
module Main where
import A
import B -- Show instance used
import C -- Show instance defined
I am not saying that this is terribly useful, I am just wondering why
it is a problem to allow it?
Paul
BTW, The above program is a translation of an idiomatic use of
functors in ML (pardon my syntax):
module A : sig type t = ... end
module B : funsig(X:SHOW where t = A.t) sig bar : A.t -> string end
module C : SHOW where t = A.t
open A
open B(C)
On Nov 21, Cale Gibbard wrote:
> data X = X deriving Show
>
> bar :: X -> String
> bar x = show x
>
> There's no need for the class constraint at all. If it's an instance
> of Show, then you're okay with just applying show to it. There's no
> need to actually assert that it's actually an instance of Show again.
>
> The only purpose of class constraints is to restrict polymorphism. If
> a function isn't polymorphic to begin with, you should never need
> them.
>
> - Cale
>
> On 21/11/05, Paul Govereau <govereau at eecs.harvard.edu> wrote:
> > Hello,
> >
> > I was hoping that someone could answer a question I have about the
> > type class system. In Haskell, I cannot write a term with an exact
> > constraint:
> >
> > > data X = X
> > > bar :: Show X => X -> String
> > > bar x = show x
> >
> > According to the Haskell 98 report, a qualifier can only be applied to
> > type variables, but I don't see where the trouble is. The term seems
> > to have reasonable type, and I don't see any reason why the
> > dictionary-passing translation shouldn't work out; I am wondering what
> > problems you run into if this restriction is lifted?
> >
> > Note, with GHC and Glasgow extensions you can write this program:
> >
> > > data Y a = Y
> > > foo :: Show (Y a) => Y a -> String
> > > foo x = show x
> >
> > However, the first program is still ruled out. Are there any
> > type-class experts out there that can offer an explanation?
> >
> > Thanks,
> > Paul
> > _______________________________________________
> > Haskell mailing list
> > Haskell at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell
> >
More information about the Haskell
mailing list