defaults

Cale Gibbard cgibbard at gmail.com
Thu Nov 30 08:16:42 EST 2006


On 27/11/06, Ian Lynagh <igloo at earth.li> wrote:
> On Mon, Nov 20, 2006 at 12:05:46PM +0000, Malcolm Wallace wrote:
> > Prompted by recent discussion on the Hat mailing list about the problems
> > of type-defaulting, I have added two new proposals for this issue to the
> > Haskell-prime wiki at:
> >
> >     http://hackage.haskell.org/trac/haskell-prime/wiki/Defaulting
>
> I don't see a proposal to remove defaulting defaulting altogether on
> that page - has that been discussed already?
>
> Am I the only one who puts an explicit type signature in whenever my
> compiler warns me that it is having to do some defaulting? And probably
> 99% of those would be unnecessary if (^)'s second argument was an Int,
> with a genericPower (or whatever) function providing the current type
> signature (analogous to, for example, (!!) and genericIndex).
>
> Defaulting is one wart I would be glad to be rid of.

Ack! Please, if anything, Int should be moved out of the Prelude and
provided in a module as a useful, though usually unnecessary, form of
hand-optimisation. I might be persuaded to put up with Integer being
the second argument type for (^), but I'd *really* rather it remain
polymorphic.

Splitting up the generic list operations has always seemed like a wart
in the Prelude to me. We have things like specialize pragmas now, so
it seems like a solution to a problem which is no longer there.

As for defaulting, if anything, I'd favour defaulting being
generalised to the point where it was no longer a wart. The reason
that it currently only works for numeric types is that those are the
only ones where we presently have syntax which is ambiguous right off
the bat, but people are talking about generalising the syntax for
strings and such, so that may not always be so.

I'm not yet totally convinced that this one-default-type-per-class
thing will really work, it seems to me you probably are going to want
something more general than that. However, it is moderately elegant,
and otherwise the problem of intersecting multiple defaulting lists is
an issue.

On a tangentially related note, has anyone ever written something like:
forM = flip mapM
then forgotten to give it a type signature and tried using it from the
ST monad with the monomorphism restriction on? Try the example module
below. The first time I ran into it was a few iterations of GHC ago,
and at the time I don't think the error message even mentioned the
forM, and of course, it was a much more complicated case, and it took
me a long time to track down what was happening. The MR is truly an
insidious force of evil. :)

--- MR.hs
import Control.Monad
import Control.Monad.ST
import Data.STRef

forM = flip mapM

comp v = forM [1,2,3] $ \s ->
    do x <- readSTRef v
       writeSTRef v (x + s)

main = do
    print $ runST (do
        v <- newSTRef 0
        comp v
        readSTRef v)


More information about the Haskell-prime mailing list