> Alternatively, since GHC 4.0 is there a way to run just the
> type-checker
> part of GHC 4.0 without waiting for it to compile everything?
>
> Also, has anyone manageed to build GHC4.0 for win32?
The -S flag compiles just as far as an assembly-code file, but you
can't do less than that.
3.02 has the local-forall stuff that you want as well as 4.0 (which
I disadvise for most folk ... it's still flaky).
Another workaround is to pass in several 'stringer' functions,
one to use at each type. Not beautiful, but it works.
Simon
>
> -Alex-
>
> ___________________________________________________________________
> S. Alexander Jacobson i2x Media
> 1-212-697-0184 voice 1-212-697-1427 fax
>
>
> On Mon, 26 Oct 1998, Peter Thiemann wrote:
>
> > >>>>> "Alex" == S Alexander Jacobson <[EMAIL PROTECTED]> writes:
> >
> >
> > Alex> I wrote the following function that attempts to
> generalize show by
> > Alex> allowing the user to choose the function to
> stringify constructor
> > Alex> arguments.
> >
> > >> stringArgs' sep stringer1 (MyFoo x i s) =
> > >> x' ++sep++i' ++ sep ++ s'
> > >> where
> > >> x'=stringer' x
> > >> i'=stringer'' i
> > >> s'=stringer''' s
> > >> stringer' o=stringer o
> > >> stringer'' o=stringer o
> > >> stringer''' o =stringer o
> > >> stringer o=stringer1 o --!! replacing stringer1 w/
> show works!
> >
> > Alex> This function generates a type error because
> stringer is being used as
> > Int-> Char and as Char->Char. But, if I replace
> stringer1 in the last
> > Alex> line, with the function `show`, hugs allows this function.
> >
> > OK, show :: forall a . Show a => a -> String [if my memory
> serves correctly]
> > so it is polymorphic in the type a.
> > However, the parameters of a function cannot (currently) have a
> > polymorphic type. So when you want to pass show to
> stringArgs you will
> > have to use one particular instance of this type. In the
> present case,
> > you get Show a => a -> String [note that the forall is
> gone], but you
> > cannot resolve the overloading because you do not know what
> a is. Hence
> >
> > Alex> However, if I use show and attempt to call this
> function using foo:
> >
> > >> foo x = stringArgs "\n" show (MyFoo "asd" 12 "asd")
> >
> > Alex> I get an ambiguous type signature error.
> >
> > the ambiguity. If Haskell included first-class polymorphism
> (which is
> > on the list for Haskell 2 and which is present in some form in Hugs
> > 1.3c) and you provided an explicit signature, then your function and
> > your example would work out. Modulo syntax, this is what is
> would look
> > like:
> >
> > stringArgs' :: String -> (forall a . Show a => a -> String)
> -> MyFooType -> String
> > stringArgs' sep stringer (MyFoo x i s) =
> > x' ++sep++i' ++ sep ++ s'
> > where
> > x'=stringer x
> > i'=stringer i
> > s'=stringer s
> >
> > And your function call would look just like the one above.
> >
> > -Peter
> >
>