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.
Another situation where this error may occur is when you used an explicit hole, which is a single underscore (_
) or a variable name starting with an underscore (e.g. _foo
).
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
module Main where
f x = 5
g y = x
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
module ForgotImport where
top10 :: [Int] -> [Int]
top10 = take 10 . sort
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
{-# LANGUAGE NoFieldSelectors #-}
module A (Foo (..)) where
data Foo = MkFoo { fint :: Int, fchar :: Char }
{-# LANGUAGE NoFieldSelectors #-}
module A (Foo (..)) where
data Foo = MkFoo { fint :: Int, fchar :: Char }
Example3.hs
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 }
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 }
Used a typed hole
Error Message
Example4.hs:4:7: error: [GHC-88464]
• Found hole: _ :: a -> Bool
Where: ‘a’ is a rigid type variable bound by
the type signature for:
foo :: forall a. Eq a => a -> Bool
at Example4.hs:3:1-24
• In an equation for ‘foo’: foo = _
• Relevant bindings include
foo :: a -> Bool (bound at Example4.hs:4:1)
Constraints include Eq a (from Example4.hs:3:1-24)
Valid hole fits include foo :: a -> Bool (bound at Example4.hs:4:1)
|
4 | foo = _
| ^
Description
Typed holes are very useful! They work in expressions (i.e. not in patterns or types). They generate an error, ensuring that you don’t forget to put some code there, but the error message is designed to give you information about what kind of code fits here.
Here is the GHC user’s guide on typed holes.
In the error message, the most important parts are:
- The type of the hole:
a -> Bool
in this case. - Where the type variables come from that appear in this type;
a
here comes fromfoo
’s type signature. - Relevant constraints: in this case, we know that
Eq a
holds. This list is in general not exhaustive; sometimes there are many possibly (indirectly) relevant constraints, and GHC has to make some selection of what to show. - Valid hole fits: these are suggestions from GHC of names that would typecheck in the hole. This is also in general not an exhaustive list, and typically you’ll want to write code that is not quite as simple as a single variable. In this case, GHC sees that
foo
fits — which is not terribly helpful.
Typed holes can be used for what is sometimes called type-driven programming: ask GHC what type it wants in a particular place, decide that the code should then look roughly like so (with the parts you don’t yet know filled in with holes _
again), ask GHC for the types of those holes, etc. This is mostly useful when you have very precise types in your code, typically involving some type-level programming.
If you want to test your code while you still have typed holes in your code, pass the -fdefer-typed-holes
flag to GHC. More generally, there is also the much more aggressive -fdefer-type-errors
.
Example4.hs
module Example4 where
foo :: Eq a => a -> Bool
foo = _
module Example4 where
foo :: Eq a => a -> Bool
foo x = x == x