[GHC] #11941: stage restriction mentioned when an identifier is out of scope
GHC
ghc-devs at haskell.org
Fri Apr 15 23:04:53 UTC 2016
#11941: stage restriction mentioned when an identifier is out of scope
-------------------------------------+-------------------------------------
Reporter: aavogt | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1-rc2
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
import Data.Monoid
const (return []) $ mempty { getFrst = Just () }
}}}
{{{
typeErrBug.hs:5:21: error:
• GHC stage restriction:
‘getFrst’ is used in a top-level splice, quasi-quote, or
annotation,
and must be imported, not defined locally
• In the second argument of ‘($)’, namely
‘mempty {getFrst = Just ()}’
In the expression: const (return []) $ mempty {getFrst = Just ()}
typeErrBug.hs:5:30: error:
Not in scope: ‘getFrst’
Perhaps you meant one of these:
‘getFirst’ (imported from Data.Monoid),
‘getLast’ (imported from Data.Monoid)
}}}
The stage restriction error shouldn't be mentioned: `getFrst` isn't
defined at all while the "not defined locally" phrase says it's defined
(in the wrong spot).
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11941>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list