module GHC.Parser.Header
( getImports
, mkPrelImports
, getOptionsFromFile
, getOptions
, optionsErrorMsgs
, checkProcessArgsResult
)
where
#include "HsVersions.h"
import GHC.Prelude
import GHC.Platform
import GHC.Driver.Session
import GHC.Driver.Config
import GHC.Parser.Errors.Ppr
import GHC.Parser.Errors
import GHC.Parser ( parseHeader )
import GHC.Parser.Lexer
import GHC.Hs
import GHC.Unit.Module
import GHC.Builtin.Names
import GHC.Types.Error hiding ( getErrorMessages, getWarningMessages )
import GHC.Types.SrcLoc
import GHC.Types.SourceError
import GHC.Types.SourceText
import GHC.Utils.Misc
import GHC.Utils.Outputable as Outputable
import GHC.Utils.Panic
import GHC.Utils.Monad
import GHC.Utils.Exception as Exception
import GHC.Data.StringBuffer
import GHC.Data.Maybe
import GHC.Data.Bag ( Bag, listToBag, unitBag, isEmptyBag )
import GHC.Data.FastString
import Control.Monad
import System.IO
import System.IO.Unsafe
import Data.List (partition)
getImports :: ParserOpts
-> Bool
-> StringBuffer
-> FilePath
-> FilePath
-> IO (Either
(Bag PsError)
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)],
Located ModuleName))
getImports popts implicit_prelude buf filename source_filename = do
let loc = mkRealSrcLoc (mkFastString filename) 1 1
case unP parseHeader (initParserState popts buf loc) of
PFailed pst ->
return $ Left $ getErrorMessages pst
POk pst rdr_module -> fmap Right $ do
let (_warns, errs) = getMessages pst
if not (isEmptyBag errs)
then throwIO $ mkSrcErr (fmap pprError errs)
else
let hsmod = unLoc rdr_module
mb_mod = hsmodName hsmod
imps = hsmodImports hsmod
main_loc = srcLocSpan (mkSrcLoc (mkFastString source_filename)
1 1)
mod = mb_mod `orElse` L main_loc mAIN_NAME
(src_idecls, ord_idecls) = partition ((== IsBoot) . ideclSource . unLoc) imps
ordinary_imps = filter ((/= moduleName gHC_PRIM) . unLoc
. ideclName . unLoc)
ord_idecls
implicit_imports = mkPrelImports (unLoc mod) main_loc
implicit_prelude imps
convImport (L _ i) = (fmap sl_fs (ideclPkgQual i), ideclName i)
in
return (map convImport src_idecls,
map convImport (implicit_imports ++ ordinary_imps),
mod)
mkPrelImports :: ModuleName
-> SrcSpan
-> Bool -> [LImportDecl GhcPs]
-> [LImportDecl GhcPs]
mkPrelImports this_mod loc implicit_prelude import_decls
| this_mod == pRELUDE_NAME
|| explicit_prelude_import
|| not implicit_prelude
= []
| otherwise = [preludeImportDecl]
where
explicit_prelude_import = any is_prelude_import import_decls
is_prelude_import (L _ decl) =
unLoc (ideclName decl) == pRELUDE_NAME
&& case ideclPkgQual decl of
Nothing -> True
Just b -> sl_fs b == unitIdFS baseUnitId
loc' = noAnnSrcSpan loc
preludeImportDecl :: LImportDecl GhcPs
preludeImportDecl
= L loc' $ ImportDecl { ideclExt = noAnn,
ideclSourceSrc = NoSourceText,
ideclName = L loc pRELUDE_NAME,
ideclPkgQual = Nothing,
ideclSource = NotBoot,
ideclSafe = False,
ideclQualified = NotQualified,
ideclImplicit = True,
ideclAs = Nothing,
ideclHiding = Nothing }
getOptionsFromFile :: DynFlags
-> FilePath
-> IO [Located String]
getOptionsFromFile dflags filename
= Exception.bracket
(openBinaryFile filename ReadMode)
(hClose)
(\handle -> do
opts <- fmap (getOptions' dflags)
(lazyGetToks (initParserOpts dflags') filename handle)
seqList opts $ return opts)
where
dflags' = gopt_unset dflags Opt_Haddock
blockSize :: Int
blockSize = 1024
lazyGetToks :: ParserOpts -> FilePath -> Handle -> IO [Located Token]
lazyGetToks popts filename handle = do
buf <- hGetStringBufferBlock handle blockSize
let prag_state = initPragState popts buf loc
unsafeInterleaveIO $ lazyLexBuf handle prag_state False blockSize
where
loc = mkRealSrcLoc (mkFastString filename) 1 1
lazyLexBuf :: Handle -> PState -> Bool -> Int -> IO [Located Token]
lazyLexBuf handle state eof size =
case unP (lexer False return) state of
POk state' t -> do
if atEnd (buffer state') && not eof
then getMore handle state size
else case unLoc t of
ITeof -> return [t]
_other -> do rest <- lazyLexBuf handle state' eof size
return (t : rest)
_ | not eof -> getMore handle state size
| otherwise -> return [L (mkSrcSpanPs (last_loc state)) ITeof]
getMore :: Handle -> PState -> Int -> IO [Located Token]
getMore handle state size = do
let new_size = size * 2
nextbuf <- hGetStringBufferBlock handle new_size
if (len nextbuf == 0) then lazyLexBuf handle state True new_size else do
newbuf <- appendStringBuffers (buffer state) nextbuf
unsafeInterleaveIO $ lazyLexBuf handle state{buffer=newbuf} False new_size
getToks :: ParserOpts -> FilePath -> StringBuffer -> [Located Token]
getToks popts filename buf = lexAll pstate
where
pstate = initPragState popts buf loc
loc = mkRealSrcLoc (mkFastString filename) 1 1
lexAll state = case unP (lexer False return) state of
POk _ t@(L _ ITeof) -> [t]
POk state' t -> t : lexAll state'
_ -> [L (mkSrcSpanPs (last_loc state)) ITeof]
getOptions :: DynFlags
-> StringBuffer
-> FilePath
-> [Located String]
getOptions dflags buf filename
= getOptions' dflags (getToks (initParserOpts dflags) filename buf)
getOptions' :: DynFlags
-> [Located Token]
-> [Located String]
getOptions' dflags toks
= parseToks toks
where
parseToks (open:close:xs)
| IToptions_prag str <- unLoc open
, ITclose_prag <- unLoc close
= case toArgs str of
Left _err -> optionsParseError str $
combineSrcSpans (getLoc open) (getLoc close)
Right args -> map (L (getLoc open)) args ++ parseToks xs
parseToks (open:close:xs)
| ITinclude_prag str <- unLoc open
, ITclose_prag <- unLoc close
= map (L (getLoc open)) ["-#include",removeSpaces str] ++
parseToks xs
parseToks (open:close:xs)
| ITdocOptions str _ <- unLoc open
, ITclose_prag <- unLoc close
= map (L (getLoc open)) ["-haddock-opts", removeSpaces str]
++ parseToks xs
parseToks (open:xs)
| ITlanguage_prag <- unLoc open
= parseLanguage xs
parseToks (comment:xs)
| isComment (unLoc comment)
= parseToks xs
parseToks _ = []
parseLanguage ((L loc (ITconid fs)):rest)
= checkExtension dflags (L loc fs) :
case rest of
(L _loc ITcomma):more -> parseLanguage more
(L _loc ITclose_prag):more -> parseToks more
(L loc _):_ -> languagePragParseError loc
[] -> panic "getOptions'.parseLanguage(1) went past eof token"
parseLanguage (tok:_)
= languagePragParseError (getLoc tok)
parseLanguage []
= panic "getOptions'.parseLanguage(2) went past eof token"
isComment :: Token -> Bool
isComment c =
case c of
(ITlineComment {}) -> True
(ITblockComment {}) -> True
(ITdocCommentNext {}) -> True
(ITdocCommentPrev {}) -> True
(ITdocCommentNamed {}) -> True
(ITdocSection {}) -> True
_ -> False
checkProcessArgsResult :: MonadIO m => [Located String] -> m ()
checkProcessArgsResult flags
= when (notNull flags) $
liftIO $ throwIO $ mkSrcErr $ listToBag $ map mkMsg flags
where mkMsg (L loc flag)
= mkPlainMsgEnvelope loc $
(text "unknown flag in {-# OPTIONS_GHC #-} pragma:" <+>
text flag)
checkExtension :: DynFlags -> Located FastString -> Located String
checkExtension dflags (L l ext)
= if ext' `elem` supported
then L l ("-X"++ext')
else unsupportedExtnError dflags l ext'
where
ext' = unpackFS ext
supported = supportedLanguagesAndExtensions $ platformArchOS $ targetPlatform dflags
languagePragParseError :: SrcSpan -> a
languagePragParseError loc =
throwErr loc $
vcat [ text "Cannot parse LANGUAGE pragma"
, text "Expecting comma-separated list of language options,"
, text "each starting with a capital letter"
, nest 2 (text "E.g. {-# LANGUAGE TemplateHaskell, GADTs #-}") ]
unsupportedExtnError :: DynFlags -> SrcSpan -> String -> a
unsupportedExtnError dflags loc unsup =
throwErr loc $
text "Unsupported extension: " <> text unsup $$
if null suggestions then Outputable.empty else text "Perhaps you meant" <+> quotedListWithOr (map text suggestions)
where
supported = supportedLanguagesAndExtensions $ platformArchOS $ targetPlatform dflags
suggestions = fuzzyMatch unsup supported
optionsErrorMsgs :: [String] -> [Located String] -> FilePath -> Messages DecoratedSDoc
optionsErrorMsgs unhandled_flags flags_lines _filename
= mkMessages $ listToBag (map mkMsg unhandled_flags_lines)
where unhandled_flags_lines :: [Located String]
unhandled_flags_lines = [ L l f
| f <- unhandled_flags
, L l f' <- flags_lines
, f == f' ]
mkMsg (L flagSpan flag) =
mkPlainMsgEnvelope flagSpan $
text "unknown flag in {-# OPTIONS_GHC #-} pragma:" <+> text flag
optionsParseError :: String -> SrcSpan -> a
optionsParseError str loc =
throwErr loc $
vcat [ text "Error while parsing OPTIONS_GHC pragma."
, text "Expecting whitespace-separated list of GHC options."
, text " E.g. {-# OPTIONS_GHC -Wall -O2 #-}"
, text ("Input was: " ++ show str) ]
throwErr :: SrcSpan -> SDoc -> a
throwErr loc doc =
throw $ mkSrcErr $ unitBag $ mkPlainMsgEnvelope loc doc