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

Adam Gundry adam at well-typed.com
Tue Nov 24 22:37:38 UTC 2020


Dear Todd,

On 24/11/2020 22:26, Todd Wilson wrote:
> This has got to be a trivial question, but I don't see a solution, nor
> could I find anything through searching: If I want to write a type
> declaration for the helper function g here, what do I write?
> 
>     f :: a -> [b] -> [(a,b)]
>     f a bs = g bs where
>       g :: ????
>       g [] = []
>       g (x:xs) = (a,x) : g xs

This has a disappointingly not-entirely-trivial answer:

    {-# LANGUAGE ExplicitForAll, ScopedTypeVariables #-}

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

We need the type variable `a` in the type of `g` to be the same as the
one bound in the type of `f`, but Haskell2010 doesn't have a way to
express this. The ScopedTypeVariables extension, when used with an
explicit forall, makes the type variables scope over type signatures in
the body of the function.

Hope this helps,

Adam

-- 
Adam Gundry, Haskell Consultant
Well-Typed LLP, https://www.well-typed.com/

Registered in England & Wales, OC335890
118 Wymering Mansions, Wymering Road, London W9 2NF, England


More information about the Haskell-Cafe mailing list