A partial type signature is a type signature containing special placeholders
written with a leading underscore (e.g., "_
",
"_foo
", "_bar
") called
wildcards. Partial type signatures are to type signatures
what Section 7.14, “Typed Holes” are to expressions. During compilation these
wildcards or holes will generate an error message that describes which type
was inferred at the hole's location, and information about the origin of any
free type variables. GHC reports such error messages by default.
Unlike Section 7.14, “Typed Holes”, which make the program incomplete and will generate errors when they are evaluated, this needn't be the case for holes in type signatures. The type checker is capable (in most cases) of type-checking a binding with or without a type signature. A partial type signature bridges the gap between the two extremes, the programmer can choose which parts of a type to annotate and which to leave over to the type-checker to infer.
By default, the type-checker will report an error message for each hole in a
partial type signature, informing the programmer of the inferred type. When
the -XPartialTypeSignatures
flag is enabled, the type-checker
will accept the inferred type for each hole, generating warnings instead of
errors. Additionally, these warnings can be silenced with the
-fno-warn-partial-type-signatures
flag.
A (partial) type signature has the following form: forall a b .. .
(C1, C2, ..) => tau
. It consists of three parts:
a b ..
(C1, C2, ..)
tau
We distinguish three kinds of wildcards.
Wildcards occurring within the monotype (tau) part of the type signature are
type wildcards ("type" is often omitted as this is the
default kind of wildcard). Type wildcards can be instantiated to any monotype
like Bool
or Maybe [Bool]
, including
functions and higher-kinded types like (Int -> Bool)
or
Maybe
.
not' :: Bool -> _ not' x = not x -- Inferred: Bool -> Bool maybools :: _ maybools = Just [True] -- Inferred: Maybe [Bool] just1 :: _ Int just1 = Just 1 -- Inferred: Maybe Int filterInt :: _ -> _ -> [Int] filterInt = filter -- has type forall a. (a -> Bool) -> [a] -> [a] -- Inferred: (Int -> Bool) -> [Int] -> [Int]
For instance, the first wildcard in the type signature not'
would produce the following error message:
Test.hs:4:17: Found hole ‘_’ with type: Bool To use the inferred type, enable PartialTypeSignatures In the type signature for ‘not'’: Bool -> _
When a wildcard is not instantiated to a monotype, it will be generalised
over, i.e. replaced by a fresh type variable (of which the name will often
start with w_
), e.g.
foo :: _ -> _ foo x = x -- Inferred: forall w_. w_ -> w_ filter' :: _ filter' = filter -- has type forall a. (a -> Bool) -> [a] -> [a] -- Inferred: (a -> Bool) -> [a] -> [a]
Type wildcards can also be named by giving the underscore an identifier as
suffix, i.e. _a
. These are called named
wildcards. All occurrences of the same named wildcard within one
type signature will unify to the same type. For example:
f :: _x -> _x f ('c', y) = ('d', error "Urk") -- Inferred: forall t. (Char, t) -> (Char, t)
The named wildcard forces the argument and result types to be the same.
Lacking a signature, GHC would have inferred forall a b. (Char, a) ->
(Char, b)
. A named wildcard can be mentioned in constraints,
provided it also occurs in the monotype part of the type signature to make
sure that it unifies with something:
somethingShowable :: Show _x => _x -> _ somethingShowable x = show x -- Inferred type: Show w_x => w_x -> String somethingShowable' :: Show _x => _x -> _ somethingShowable' x = show (not x) -- Inferred type: Bool -> String
Besides an extra-constraints wildcard (see Section 7.15.1.3, “Extra-Constraints Wildcard”), only named wildcards can occur in the
constraints, e.g. the _x
in Show _x
.
Named wildcards should not be confused with type variables. Even though syntactically similar, named wildcards can unify with monotypes as well as be generalised over (and behave as type variables).
In the first example above, _x
is generalised over (and is
effectively replaced by a fresh type variable w_x
). In the
second example, _x
is unified with the
Bool
type, and as Bool
implements the
Show
type class, the constraint Show
Bool
can be simplified away.
By default, GHC (as the Haskell 2010 standard prescribes) parses identifiers
starting with an underscore in a type as type variables. To treat them as
named wildcards, the -XNamedWildCards
flag should be enabled.
The example below demonstrated the effect.
foo :: _a -> _a foo _ = False
Compiling this program without enabling -XNamedWildCards
produces the following error message complaining about the type variable
_a
no matching the actual type Bool
.
Test.hs:5:9: Couldn't match expected type ‘_a’ with actual type ‘Bool’ ‘_a’ is a rigid type variable bound by the type signature for foo :: _a -> _a at Test.hs:4:8 Relevant bindings include foo :: _a -> _a (bound at Test.hs:4:1) In the expression: False In an equation for ‘foo’: foo _ = False
Compiling this program with -XNamedWildCards
enabled produces
the following error message reporting the inferred type of the named wildcard
_a
.
Test.hs:4:8: Warning: Found hole ‘_a’ with type: Bool In the type signature for ‘foo’: _a -> _a
The third kind of wildcard is the extra-constraints wildcard. The presence of an extra-constraints wildcard indicates that an arbitrary number of extra constraints may be inferred during type checking and will be added to the type signature. In the example below, the extra-constraints wildcard is used to infer three extra constraints.
arbitCs :: _ => a -> String arbitCs x = show (succ x) ++ show (x == x) -- Inferred: -- forall a. (Enum a, Eq a, Show a) => a -> String -- Error: Test.hs:5:12: Found hole ‘_’ with inferred constraints: (Enum a, Eq a, Show a) To use the inferred type, enable PartialTypeSignatures In the type signature for ‘arbitCs’: _ => a -> String
An extra-constraints wildcard shouldn't prevent the programmer from already listing the constraints he knows or wants to annotate, e.g.
-- Also a correct partial type signature: arbitCs' :: (Enum a, _) => a -> String arbitCs' x = arbitCs x -- Inferred: -- forall a. (Enum a, Show a, Eq a) => a -> String -- Error: Test.hs:9:22: Found hole ‘_’ with inferred constraints: (Eq a, Show a) To use the inferred type, enable PartialTypeSignatures In the type signature for ‘arbitCs'’: (Enum a, _) => a -> String
An extra-constraints wildcard can also lead to zero extra constraints to be inferred, e.g.
noCs :: _ => String noCs = "noCs" -- Inferred: String -- Error: Test.hs:13:9: Found hole ‘_’ with inferred constraints: () To use the inferred type, enable PartialTypeSignatures In the type signature for ‘noCs’: _ => String
As a single extra-constraints wildcard is enough to infer any number of constraints, only one is allowed in a type signature and it should come last in the list of constraints.
Extra-constraints wildcards cannot be named.
Partial type signatures are allowed for bindings, pattern and expression signatures. In all other contexts, e.g. type class or type family declarations, they are disallowed. In the following example a wildcard is used in each of the three possible contexts.
{-# LANGUAGE ScopedTypeVariables #-} foo :: _ foo (x :: _) = (x :: _) -- Inferred: forall w_. w_ -> w_