(Adam might be surprised at this, but I won’t burden that discussion any further.) Consider:
{-# LANGUAGE PartialTypeSignatures, NamedWildCards, ExplicitForAll #-}
-- ScopedTypeVariables,
module NamedWildCards where
f2 :: [a] -> [a] -- forall a.
f2 xs = ys ++ ys :: _aa
where ys :: [_aa]
ys = reverse xs :: _aa
I was expecting GHC to reject this: NamedWildCard _aa
used at inconsistent types (occurs check), but no. If I switch on ScopedTypeVariables
, then it warns me – even without the ExplicitForAll
on f2
, or indeed without any signature at all for f2
.
Is this behaviour what anybody out there expects?
But! But! I was using the NamedWildCard
mechanism precisely to avoid the scope pollution from ScopedTypeVariables
and yet annotate my types. (I can’t declare a fresh tyvar within the body of the where
: rigid type variable
rejections.)
The term-level names declared on RHS of the where
scope also ‘backwards’ to its left – that is the RHS of f2
's equation. That is the precise purpose of where
. Then I expect tyvars to have the same scoping.
(Yes I know I’ll soon be able to accomplish this with TypeAbstractions
. No that doesn’t persuade me one jot. The way I’d prefer to do this is with a tyvar annotation on f2
's LHS where other names get bound: parameter xs
– but needs bl…y ScopedTypeVariables
, and/or ResultTypeSignatures
– still in bl…y development pipeline.)