Too many type arguments in constructor pattern [GHC-01629]
Every type application has to be “consumed” by a type variable in the
corresponding type. Just as it is an error to pass more than one argument to putStrLn
, it is also an error to apply more types than there are
type variables in a type. For instance, if a type has only 1 type parameter (e.g. Maybe a
), we can only apply 1 type argument (e.g. applying @Int
to produce Maybe Int
); there is no unbound type parameter present for further applications.
Examples
Too many type arguments in constructor pattern
The @Bool
is too much in this example. There is nothing to bind to it, so it is not allowed to be there.
Error Message
TyArgs.hs:6:4: error: [GHC-01629]
• Too many type arguments in constructor pattern for ‘Just’
Expected no more than 1; got 2
• In the pattern: Just @Int @Bool x
In an equation for ‘f’: f (Just @Int @Bool x) = x
|
6 | f (Just @Int @Bool x) = x
| ^^^^^^^^^^^^^^^^^
TyArgs.hs
Before
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module TyArgs where
f :: Maybe Int -> Int
f (Just @Int @Bool x) = x
f Nothing = 10
After
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module TyArgs where
f :: Maybe Int -> Int
f (Just @Int x) = x
f Nothing = 10