Not in scope [GHC-76037]

An identifier can only be used if it is in scope; i.e. if it is bound or declared previously and that binding/declaration is available at the usage location.

Examples

Unbound data constructor in lambda

The data constructor A used in the lambda expression is not in scope.

Error Message

NotInScopeLambda.hs:3:6: error: [GHC-76037]
    Not in scope: data constructor ‘A’
  |
3 | f = \A -> A
  |      ^
NotInScopeLambda.hs
Before
module NotInScopeLambda where

f = \A -> A
After
module NotInScopeLambda where

data Foo = A | B

f :: Foo -> Foo
f = \A -> A
Unbound class name

The class name B referenced in the definition of class C is not in scope.

Error Message

NotInScopeClass.hs:3:8: error: [GHC-76037]
    Not in scope: type constructor or class ‘B’
  |
3 | class (B a) => C a where
  |        ^
NotInScopeClass.hs
Before
module NotInScopeClass where

class (B a) => C a where
 op1 :: a -> Int
After
module NotInScopeClass where

class B a where
  op :: a -> a

class (B a) => C a where
 op1 :: a -> Int
Data constructor not imported

The import statement import Foo (Bar) imports the Bar data type, but not its constructor MkBar. As such, the constructor is not in scope.

Error Message

IncorrectImport.hs:6:12: error: [GHC-76037]
    Not in scope: data constructor ‘MkBar’
  |
6 | barAddOne (MkBar n) = MkBar (n + 1)
  |            ^^^^^
IncorrectImport.hs
Before
module IncorrectImport where

import Foo (Bar)

barAddOne :: Bar -> Bar
barAddOne (MkBar n) = MkBar (n + 1)
After
module IncorrectImport where

import Foo (Bar(..))

barAddOne :: Bar -> Bar
barAddOne (MkBar n) = MkBar (n + 1)