[Haskell-cafe] Types of partially instantiated polymorphic helper functions

Viktor Dukhovni ietf-dane at dukhovni.org
Tue Nov 24 23:38:30 UTC 2020


On Tue, Nov 24, 2020 at 02:58:33PM -0800, Todd Wilson wrote:

> I see, thanks! And I guess that if the type variable c in your type of g
> were changed to b, it will still work, but now g would have a monomorphic
> instead of polymorphic type.

Yes, exactly.  I was not going to post my otherwise redundant
answer, but since it in fact makes `g` monomorphic, here it is:

The simplest thing (which you probably already know) is to not give `g`                                                                                                                      a type signature, and let GHC infer the type.  But since you asked,                                                                                                                          one solution is:

    {-# LANGUAGE ScopedTypeVariables #-}

    f :: forall a b. a -> [b] -> [(a, b)]
    f a bs = g bs where
      g :: [b] -> [(a, b)]
      g [] = []
      g (x:xs) = (a, x) : g xs

You need scoped type variables becase the `a` in the return-type of `g`
needs to be the *same* `a` as in the signature of `f`, and unlike `f`
the function `g` is not polymorphic in `a`, so you need a mechanis to
identify the two instances of the type variable, and that's where the
`ScopedTypeVariables` pragma comes into play.

Once you have `ScopedTypeVariables`, you also get (for free)
`ExplicitForall`, and each new universally quanitified type
variable now needs "forall" to bring it into scope.

-- 
    Viktor.


More information about the Haskell-Cafe mailing list