Type signature lacks an accompanying binding [GHC-44432]
If a type signature is given for a name, then that name also needs to be defined.
Examples
Type signature lacks an accompanying binding
If a type signature is given for a name in a local let expression, then the name also needs to be defined.
In this example, a type signature was given for the name two
in a let expression, but no definition was specified.
This error can be fixed by adding a definition which accompanies the type signature.
Error Message
MissingBinding.hs:6:5: error: [GHC-44432]
The type signature for ‘two’ lacks an accompanying binding
|
6 | two :: Integer
| ^^^
MissingBinding.hs
module MissingBinding where
fortytwo :: Integer
fortytwo =
let
two :: Integer
in
40 + two
module MissingBinding where
fortytwo :: Integer
fortytwo =
let
two :: Integer
two = 2
in
40 + two
Type signature lacks an accompanying binding
If a type signature is given for a name in a Haskell module, then the name also needs to be defined.
In this example, a type signature was given for the name someBoolean
in a Haskell module, but no definition was specified.
This error can be fixed by adding a definition which accompanies the type signature.
Error Message
MissingBinding.hs:3:1: error: [GHC-44432]
The type signature for ‘someBoolean’ lacks an accompanying binding
|
3 | someBoolean :: Bool
| ^^^^^^^^^^^
MissingBinding.hs
module MissingBinding where
someBoolean :: Bool
module MissingBinding where
someBoolean :: Bool
someBoolean = True
Type signature lacks an accompanying binding
If a type signature is given for a name in a Haskell module, then the name also needs to be defined.
In this example, the programmer misspelt the name factorial
.
GHC helpfully suggests that fatcorial
might be the intended spelling.
The error can be fixed by correcting the typo.
Error Message
MissingBinding.hs:5:1: error: [GHC-44432]
The type signature for ‘factorial’ lacks an accompanying binding
Suggested fix: Perhaps use ‘fatcorial’ (Defined at Main.hs:6:1)
|
5 | factorial :: Natural -> Natural
| ^^^^^^^^^
MissingBinding.hs
module MissingBinding where
import Numeric.Natural
factorial :: Natural -> Natural
fatcorial n
| n == 0 = 1
| otherwise = n * factorial (n - 1)
module MissingBinding where
import Numeric.Natural
factorial :: Natural -> Natural
factorial n
| n == 0 = 1
| otherwise = n * factorial (n - 1)
Type signature lacks an accompanying binding
If a type signature is given for a name in a where clause, then the name also needs to be defined.
In this example, a type signature was given for the name two
in a where clause, but no definition was specified.
This error can be fixed by adding a definition which accompanies the type signature.
Error Message
MissingBinding.hs:6:5: error: [GHC-44432]
The type signature for ‘two’ lacks an accompanying binding
|
6 | two :: Integer
| ^^^
MissingBinding.hs
module MissingBinding where
fortytwo :: Integer
fortytwo = 40 + two
where
two :: Integer
module MissingBinding where
fortytwo :: Integer
fortytwo = 40 + two
where
two :: Integer
two = 2