lifting functions to tuples?

Abraham Egnor aegnor at antioch-college.edu
Tue Nov 18 10:46:43 EST 2003


The classic way to write a lift function for tuples is, of course:

liftTup f (a, b) = (f a, f b)

which has a type of (a -> b) -> (a, a) -> (b, b).  I've been wondering if
it would be possible to write a function that doesn't require the types in
the tuple to be the same, just that the types in the second tuple are the
result of applying the type transformation implied in the function to be
lifted to the types in the first tuple.  Now, in Haskell98, this isn't
possible because of the monomorphism restriction; however, ghc
conveniently has a way to disable that.  However, I'm still having
problems figuring out if it's even doable within the current constraints
of the glasgow-extended type system.  One possibility I tried is:

liftTup (f :: forall a b. a -> b) (p, q) = (f p, f q)

which does, in fact, compile.  A very odd type is inferred:

liftTup :: forall b1 b a1 a. (forall a2 b2. a2 -> b2) -> (a, a1) -> (b, b1)

I call this odd because there's no mention of the type dependencies
inherent in the actual function.  However, any attempt to apply it to a
polymorphic function results in the following errors:

random.hs:17:
    Could not deduce (Num b) from the context ()
      arising from use of `inc' at random.hs:17
    Probable fix:
        Add (Num b) to the expected type of an expression
    In the first argument of `liftTup', namely `inc'
    In the definition of `tupInc': tupInc = liftTup inc

random.hs:17:
    Inferred type is less polymorphic than expected
        Quantified type variable `b' is unified with another quantified
type variable `a'
    In the first argument of `liftTup', namely `inc'
    In the definition of `tupInc': tupInc = liftTup inc

which seems to be a direct consequence of the odd derived type.  However,
I can't think of a way to write a better one.  The problem, as far as I
can tell, is that there's no way in the type system to deal in type
transformations, i.e. apply the conversion implied by (a -> b) to a given
type a' to produce the appropriate b'.

Thoughts?

Abe



More information about the Haskell mailing list