This error is not yet tested in the GHC testsuite. So I'm trying to figure out how to trigger it.
In compiler/GHC/Tc/Errors/Types.hs:
{-| TcRnExpectedValueId is an error occurring when something that is not a
value identifier is used where one is expected.
Example(s): none
Test cases: none
-}
TcRnExpectedValueId :: !TcTyThing -> TcRnMessage
In compiler/GHC/Tc/Errors/Ppr.hs:
TcRnExpectedValueId thing
-> mkSimpleDecorated $
ppr thing <+> text "used where a value identifier was expected"
In compiler/GHC/Tc/Gen/Head.hs:
tcInferRecSelId :: FieldOcc GhcRn
-> TcM (HsExpr GhcTc, TcSigmaType)
tcInferRecSelId (FieldOcc sel_name lbl)
= do { sel_id <- tc_rec_sel_id
; let expr = HsRecSel noExtField (FieldOcc sel_id lbl)
; return (expr, idType sel_id)
}
where
occ :: OccName
occ = rdrNameOcc (unLoc lbl)
tc_rec_sel_id :: TcM TcId
-- Like tc_infer_id, but returns an Id not a HsExpr,
-- so we can wrap it back up into a HsRecSel
tc_rec_sel_id
= do { thing <- tcLookup sel_name
; case thing of
ATcId { tct_id = id }
-> do { check_naughty occ id -- See Note [Local record selectors]
; check_local_id id
; return id }
AGlobal (AnId id)
-> do { check_naughty occ id
; return id }
-- A global cannot possibly be ill-staged
-- nor does it need the 'lifting' treatment
-- hence no checkTh stuff here
_ -> failWithTc $ TcRnExpectedValueId thing }
and
tc_infer_id :: Name -> TcM (HsExpr GhcTc, TcSigmaType)
tc_infer_id id_name
= do { thing <- tcLookup id_name
; case thing of
ATcId { tct_id = id }
-> do { check_local_id id
; return_id id }
AGlobal (AnId id) -> return_id id
-- A global cannot possibly be ill-staged
-- nor does it need the 'lifting' treatment
-- Hence no checkTh stuff here
AGlobal (AConLike (RealDataCon con)) -> tcInferDataCon con
AGlobal (AConLike (PatSynCon ps)) -> tcInferPatSyn id_name ps
(tcTyThingTyCon_maybe -> Just tc) -> fail_tycon tc -- TyCon or TcTyCon
ATyVar name _ -> fail_tyvar name
_ -> failWithTc $ TcRnExpectedValueId thing }
where
fail_tycon tc = do
gre <- getGlobalRdrEnv
let nm = tyConName tc
pprov = case lookupGRE_Name gre nm of
Just gre -> nest 2 (pprNameProvenance gre)
Nothing -> empty
fail_with_msg dataName nm pprov
fail_tyvar nm =
let pprov = nest 2 (text "bound at" <+> ppr (getSrcLoc nm))
in fail_with_msg varName nm pprov
fail_with_msg whatName nm pprov = do
(import_errs, hints) <- get_suggestions whatName
unit_state <- hsc_units <$> getTopEnv
let
-- TODO: unfortunate to have to convert to SDoc here.
-- This should go away once we refactor ErrInfo.
hint_msg = vcat $ map ppr hints
import_err_msg = vcat $ map ppr import_errs
info = ErrInfo { errInfoContext = pprov, errInfoSupplementary = import_err_msg $$ hint_msg }
failWithTc $ TcRnMessageWithInfo unit_state (
mkDetailedMessage info (TcRnIncorrectNameSpace nm False))
get_suggestions ns = do
let occ = mkOccNameFS ns (occNameFS (occName id_name))
lcl_env <- getLocalRdrEnv
unknownNameSuggestions lcl_env WL_Anything (mkRdrUnqual occ)
return_id id = return (HsVar noExtField (noLocA id), idType id)
This error is not yet tested in the GHC testsuite. So I'm trying to figure out how to trigger it.
In
compiler/GHC/Tc/Errors/Types.hs
:In
compiler/GHC/Tc/Errors/Ppr.hs
:In
compiler/GHC/Tc/Gen/Head.hs
:and