Mutually recursive bindings

Tom Pledger Tom.Pledger@peace.com
Mon, 6 Nov 2000 11:49:56 +1300 (NZDT)


Hi.

For this code (an example from the Combined Binding Groups section of
Mark Jones's "Typing Haskell in Haskell"):

    f  :: Eq a => a -> Bool
    f x = (x == x) || g True
    g y = (y <= y) || f True

Haskell infers the type:

    g  :: Ord a => a -> Bool

but if the explicit type signature for f is removed, we get:

    f, g :: Bool -> Bool

So, why do both GHC and Classic Hugs accept the following program?

    module Main where

    fFix g x = (x == x) || g True
    gFix f y = (y <= y) || f True

    fMono x = fFix gMono x
    gMono y = gFix fMono y

    f     x = fFix gMono x
    g     y = gFix fMono y

    main = print (f "I am not a Boolean.")

They both reject it if fMono replaces f in the last line.  But the
transformation seemed quite mechanical: move the guts of the mutually
recursive functions into new non-recursive functions, and define new
polymorphic functions which look like repeats of the monomorphic
mutually recursive functions.

Would it be an outright win to have this done automatically?

Regards,
Tom