Bad import not exported [GHC-61689]
This error is triggered when importing a symbol that the module does not export.
Examples
Importing an unexported symbol.
Message
SymbolNotExported.hs:3:16: error: [GHC-61689]
Module ‘A’ does not export ‘two’.
|
3 | import A (one, two)
| ^^^
Explanation
The module SymbolNotExported
imports the symbol two
even though A
does not export it.
The fix is to remove the bad import.
A.hs
Before
module A (one) where
one :: ()
one = ()
two :: ()
two = ()
After
module A (one) where
one :: ()
one = ()
two :: ()
two = ()
SymbolNotExported.hs
Before
module SymbolNotExported where
import A (one, two)
After
module SymbolNotExported where
import A (one)
Importing a field selector that has been disabled with NoFieldSelectors.
Message
NoFieldSelectors.hs:3:24: error: [GHC-61689]
Module ‘A’ does not export ‘fint’.
Suggested fix:
Notice that ‘fint’ is a field selector belonging to the type ‘A.Foo’
that has been suppressed by NoFieldSelectors.
|
3 | import A (Foo (MkFoo), fint)
| ^^^^
Explanation
With FieldSelectors
(the default), field selectors are exported such that the following two imports are equivalent:
import A (Foo (MkFoo, fint))
import A (Foo (MkFoo), fint)
With NoFieldSelectors
at the definition site (A.hs
), the second example is always an error:
import A (Foo (MkFoo), fint)
The fix is to move the selector import to the type or remove it altogether.
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 }
NoFieldSelectors.hs
Before
module NoFieldSelectors where
import A (Foo (MkFoo), fint)
After
module NoFieldSelectors where
import A (Foo (MkFoo, fint))