[Haskell-cafe] Types of partially instantiated polymorphic helper functions
Henning Thielemann
lemming at henning-thielemann.de
Tue Nov 24 23:50:58 UTC 2020
On Tue, 24 Nov 2020, Viktor Dukhovni wrote:
> 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
An alternative would be to let g be polymorphic but add 'a' as parameter:
f a bs = g a bs where
g :: a -> [b] -> [(a, b)]
g = map ((,) a)
More information about the Haskell-Cafe
mailing list