7.14. Scoped Type Variables

A pattern type signature can introduce a scoped type variable. For example

f (xs::[a]) = ys ++ ys
           where
              ys :: [a]
              ys = reverse xs

The pattern (xs::[a]) includes a type signature for xs. This brings the type variable a into scope; it scopes over all the patterns and right hand sides for this equation for f. In particular, it is in scope at the type signature for y.

Pattern type signatures are completely orthogonal to ordinary, separate type signatures. The two can be used independently or together. At ordinary type signatures, such as that for ys, any type variables mentioned in the type signature that are not in scope are implicitly universally quantified. (If there are no type variables in scope, all type variables mentioned in the signature are universally quantified, which is just as in Haskell 98.) In this case, since a is in scope, it is not universally quantified, so the type of ys is the same as that of xs. In Haskell 98 it is not possible to declare a type for ys; a major benefit of scoped type variables is that it becomes possible to do so.

Scoped type variables are implemented in both GHC and Hugs. Where the implementations differ from the specification below, those differences are noted.

So much for the basic idea. Here are the details.

7.14.1. What a pattern type signature means

A type variable brought into scope by a pattern type signature is simply the name for a type. The restriction they express is that all occurrences of the same name mean the same type. For example:
  f :: [Int] -> Int -> Int
  f (xs::[a]) (y::a) = (head xs + y) :: a
The pattern type signatures on the left hand side of f express the fact that xs must be a list of things of some type a; and that y must have this same type. The type signature on the expression (head xs) specifies that this expression must have the same type a. There is no requirement that the type named by "a" is in fact a type variable. Indeed, in this case, the type named by "a" is Int. (This is a slight liberalisation from the original rather complex rules, which specified that a pattern-bound type variable should be universally quantified.) For example, all of these are legal:

  t (x::a) (y::a) = x+y*2

  f (x::a) (y::b) = [x,y]       -- a unifies with b

  g (x::a) = x + 1::Int         -- a unifies with Int

  h x = let k (y::a) = [x,y]    -- a is free in the
        in k x                  -- environment

  k (x::a) True    = ...        -- a unifies with Int
  k (x::Int) False = ...

  w :: [b] -> [b]
  w (x::a) = x                  -- a unifies with [b]

7.14.2. Scope and implicit quantification

7.14.3. Result type signatures

Result type signatures are not yet implemented in Hugs.

7.14.4. Where a pattern type signature can occur

A pattern type signature can occur in any pattern, but there are restrictions on pattern bindings:

Such degnerate function bindings do not fall under the monomorphism restriction. Thus:

  g :: a -> a -> Bool = \x y. x==y

Here g has type forall a. Eq a => a -> a -> Bool, just as if g had a separate type signature. Lacking a type signature, g would get a monomorphic type.