module TcAnnotations ( tcAnnotations, annCtxt ) where
#ifdef GHCI
import TcSplice ( runAnnotation )
import Module
import DynFlags
import Control.Monad ( when )
#else
import DynFlags ( WarnReason(NoReason) )
#endif
import HsSyn
import Annotations
import Name
import TcRnMonad
import SrcLoc
import Outputable
#ifndef GHCI
tcAnnotations :: [LAnnDecl Name] -> TcM [Annotation]
tcAnnotations [] = return []
tcAnnotations anns@(L loc _ : _)
= do { setSrcSpan loc $ addWarnTc NoReason $
(text "Ignoring ANN annotation" <> plural anns <> comma
<+> text "because this is a stage-1 compiler or doesn't support GHCi")
; return [] }
#else
tcAnnotations :: [LAnnDecl Name] -> TcM [Annotation]
tcAnnotations anns = mapM tcAnnotation anns
tcAnnotation :: LAnnDecl Name -> TcM Annotation
tcAnnotation (L loc ann@(HsAnnotation _ provenance expr)) = do
mod <- getModule
let target = annProvenanceToTarget mod provenance
setSrcSpan loc $ addErrCtxt (annCtxt ann) $ do
dflags <- getDynFlags
when (safeLanguageOn dflags) $ failWithTc safeHsErr
runAnnotation target expr
where
safeHsErr = vcat [ text "Annotations are not compatible with Safe Haskell."
, text "See https://ghc.haskell.org/trac/ghc/ticket/10826" ]
annProvenanceToTarget :: Module -> AnnProvenance Name -> AnnTarget Name
annProvenanceToTarget _ (ValueAnnProvenance (L _ name)) = NamedTarget name
annProvenanceToTarget _ (TypeAnnProvenance (L _ name)) = NamedTarget name
annProvenanceToTarget mod ModuleAnnProvenance = ModuleTarget mod
#endif
annCtxt :: OutputableBndr id => AnnDecl id -> SDoc
annCtxt ann
= hang (text "In the annotation:") 2 (ppr ann)