Variable not in scope [GHC-88464]

This error means that a variable name used in a program can’t be matched up with a corresponding binding site.

In Haskell, every variable comes into existence at a specific location. Examples include function argument names, local definitions with let, and module-level definitions. Creating a new name like this is called binding it, and the area of the program that can refer to the new name is called its scope. The message means that the provided name is not available for reference right where it is referred to.

A common situation where this error occurs is when the programmer forgets to import some name from a module. In that case, the solution is to add the missing import declaration.

Example error text

error: [GHC-88464] Variable not in scope: x
error: [GHC-88464] Variable not in scope: sort :: [Int] -> [Int]

Examples

Attempted to refer to another function's argument

Error Message

Main.hs:5:7: error: [GHC-88464]
    Variable not in scope: x
  |
5 | g y = x
  |       ^

Description

In this example, the body of g attempts to refer to x, which is an argument to f and thus not available. The updated version renames g’s argument so that the x in the body can refer to it.

Main.hs
Before
module Main where

f x = 5

g y = x
After
module Main where

f x = 5

g x = x
Forgetting an import declaration

Error Message

ForgotImport.hs:4:19: error: [GHC-88464]
    Variable not in scope: sort :: [Int] -> [Int]
    Suggested fix: Perhaps use ‘sqrt’ (imported from Prelude)
  |
4 | top10 = take 10 . sort
  |                   ^^^^

Description

In this example, the programmer forgot to import the sort function from the Data.List module. The updated version adds the appropriate import declaration.

ForgotImport.hs
Before
module ForgotImport where

top10 :: [Int] -> [Int]
top10 = take 10 . sort
After
module ForgotImport where

import Data.List (sort)

top10 :: [Int] -> [Int]
top10 = take 10 . sort
Attempted to use a field selector disabled with NoFieldSelectors

Error Message

Example3.hs:14:13: error: [GHC-88464]
    Variable not in scope: fint :: Foo -> Int
    Suggested fix:
      Notice that ‘fint’ is a field selector belonging to the type ‘Foo’
      that has been suppressed by NoFieldSelectors.
   |
14 | getFooInt = fint
   |             ^^^^

Description

This example attempts to use the field selector fint, despite it being disabled at the definition site (A.hs) with NoFieldSelectors. This fix is to use pattern matching instead.

Notice that record creation and updates still work with NoFieldSelectors.

A.hs
Before
{-# LANGUAGE NoFieldSelectors #-}

module A (Foo (..)) where

data Foo = MkFoo { fint :: Int, fchar :: Char }
After
{-# LANGUAGE NoFieldSelectors #-}

module A (Foo (..)) where

data Foo = MkFoo { fint :: Int, fchar :: Char }
Example3.hs
Before
module Example3 where

import A (Foo (MkFoo, fint, fchar))

getFooInt :: Foo -> Int
getFooInt = fint -- this is the problem

-- Creation and updates below are fine

mkFoo :: Foo
mkFoo =
  MkFoo
    { fint = 0,
      fchar = 'a'
    }

setFooInt :: Foo -> Int -> Foo
setFooInt f x = f { fint = x }
After
module Example3 where

import A (Foo (MkFoo, fint, fchar))

getFooInt :: Foo -> Int
getFooInt (MkFoo i _) = i -- this is fine

-- Creation and updates below are fine

mkFoo :: Foo
mkFoo =
  MkFoo
    { fint = 0,
      fchar = 'a'
    }

setFooInt :: Foo -> Int -> Foo
setFooInt f x = f { fint = x }