{-# LANGUAGE CPP #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE TypeFamilies #-}
module HeaderInfo ( getImports
, mkPrelImports
, getOptionsFromFile, getOptions
, optionsErrorMsgs,
checkProcessArgsResult ) where
#include "HsVersions.h"
import GhcPrelude
import HscTypes
import Parser ( parseHeader )
import Lexer
import FastString
import HsSyn
import Module
import PrelNames
import StringBuffer
import SrcLoc
import DynFlags
import ErrUtils
import Util
import Outputable
import Pretty ()
import Maybes
import Bag ( emptyBag, listToBag, unitBag )
import MonadUtils
import Exception
import BasicTypes
import qualified GHC.LanguageExtensions as LangExt
import Control.Monad
import System.IO
import System.IO.Unsafe
import Data.List
getImports :: DynFlags
-> StringBuffer
-> FilePath
-> FilePath
-> IO (Either
ErrorMessages
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)],
Located ModuleName))
getImports :: DynFlags
-> StringBuffer
-> FilePath
-> FilePath
-> IO
(Either
ErrorMessages
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName))
getImports dflags :: DynFlags
dflags buf :: StringBuffer
buf filename :: FilePath
filename source_filename :: FilePath
source_filename = do
let loc :: RealSrcLoc
loc = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc (FilePath -> FastString
mkFastString FilePath
filename) 1 1
case P (Located (HsModule GhcPs))
-> PState -> ParseResult (Located (HsModule GhcPs))
forall a. P a -> PState -> ParseResult a
unP P (Located (HsModule GhcPs))
parseHeader (DynFlags -> StringBuffer -> RealSrcLoc -> PState
mkPState DynFlags
dflags StringBuffer
buf RealSrcLoc
loc) of
PFailed _ span :: SrcSpan
span err :: MsgDoc
err -> do
Either
ErrorMessages
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName)
-> IO
(Either
ErrorMessages
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName))
forall (m :: * -> *) a. Monad m => a -> m a
return (Either
ErrorMessages
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName)
-> IO
(Either
ErrorMessages
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName)))
-> Either
ErrorMessages
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName)
-> IO
(Either
ErrorMessages
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName))
forall a b. (a -> b) -> a -> b
$ ErrorMessages
-> Either
ErrorMessages
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName)
forall a b. a -> Either a b
Left (ErrorMessages
-> Either
ErrorMessages
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName))
-> ErrorMessages
-> Either
ErrorMessages
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName)
forall a b. (a -> b) -> a -> b
$ ErrMsg -> ErrorMessages
forall a. a -> Bag a
unitBag (ErrMsg -> ErrorMessages) -> ErrMsg -> ErrorMessages
forall a b. (a -> b) -> a -> b
$ DynFlags -> SrcSpan -> MsgDoc -> ErrMsg
mkPlainErrMsg DynFlags
dflags SrcSpan
span MsgDoc
err
POk pst :: PState
pst rdr_module :: Located (HsModule GhcPs)
rdr_module -> (([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName)
-> Either
ErrorMessages
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName))
-> IO
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName)
-> IO
(Either
ErrorMessages
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName)
-> Either
ErrorMessages
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName)
forall a b. b -> Either a b
Right (IO
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName)
-> IO
(Either
ErrorMessages
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName)))
-> IO
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName)
-> IO
(Either
ErrorMessages
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName))
forall a b. (a -> b) -> a -> b
$ do
let _ms :: (ErrorMessages, ErrorMessages)
_ms@(_warns :: ErrorMessages
_warns, errs :: ErrorMessages
errs) = PState -> DynFlags -> (ErrorMessages, ErrorMessages)
getMessages PState
pst DynFlags
dflags
ms :: (ErrorMessages, ErrorMessages)
ms = (ErrorMessages
forall a. Bag a
emptyBag, ErrorMessages
errs)
if DynFlags -> (ErrorMessages, ErrorMessages) -> Bool
errorsFound DynFlags
dflags (ErrorMessages, ErrorMessages)
ms
then SourceError
-> IO
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName)
forall e a. Exception e => e -> IO a
throwIO (SourceError
-> IO
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName))
-> SourceError
-> IO
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName)
forall a b. (a -> b) -> a -> b
$ ErrorMessages -> SourceError
mkSrcErr ErrorMessages
errs
else
let hsmod :: SrcSpanLess (Located (HsModule GhcPs))
hsmod = Located (HsModule GhcPs) -> SrcSpanLess (Located (HsModule GhcPs))
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located (HsModule GhcPs)
rdr_module
mb_mod :: Maybe (Located ModuleName)
mb_mod = HsModule GhcPs -> Maybe (Located ModuleName)
forall pass. HsModule pass -> Maybe (Located ModuleName)
hsmodName SrcSpanLess (Located (HsModule GhcPs))
HsModule GhcPs
hsmod
imps :: [LImportDecl GhcPs]
imps = HsModule GhcPs -> [LImportDecl GhcPs]
forall pass. HsModule pass -> [LImportDecl pass]
hsmodImports SrcSpanLess (Located (HsModule GhcPs))
HsModule GhcPs
hsmod
main_loc :: SrcSpan
main_loc = SrcLoc -> SrcSpan
srcLocSpan (FastString -> Int -> Int -> SrcLoc
mkSrcLoc (FilePath -> FastString
mkFastString FilePath
source_filename)
1 1)
mod :: Located ModuleName
mod = Maybe (Located ModuleName)
mb_mod Maybe (Located ModuleName)
-> Located ModuleName -> Located ModuleName
forall a. Maybe a -> a -> a
`orElse` SrcSpan -> SrcSpanLess (Located ModuleName) -> Located ModuleName
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
main_loc ModuleName
SrcSpanLess (Located ModuleName)
mAIN_NAME
(src_idecls :: [LImportDecl GhcPs]
src_idecls, ord_idecls :: [LImportDecl GhcPs]
ord_idecls) = (LImportDecl GhcPs -> Bool)
-> [LImportDecl GhcPs]
-> ([LImportDecl GhcPs], [LImportDecl GhcPs])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition (ImportDecl GhcPs -> Bool
forall pass. ImportDecl pass -> Bool
ideclSource(ImportDecl GhcPs -> Bool)
-> (LImportDecl GhcPs -> ImportDecl GhcPs)
-> LImportDecl GhcPs
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.LImportDecl GhcPs -> ImportDecl GhcPs
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc) [LImportDecl GhcPs]
imps
ordinary_imps :: [LImportDecl GhcPs]
ordinary_imps = (LImportDecl GhcPs -> Bool)
-> [LImportDecl GhcPs] -> [LImportDecl GhcPs]
forall a. (a -> Bool) -> [a] -> [a]
filter ((ModuleName -> ModuleName -> Bool
forall a. Eq a => a -> a -> Bool
/= Module -> ModuleName
moduleName Module
gHC_PRIM) (ModuleName -> Bool)
-> (LImportDecl GhcPs -> ModuleName) -> LImportDecl GhcPs -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Located ModuleName -> ModuleName
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc
(Located ModuleName -> ModuleName)
-> (LImportDecl GhcPs -> Located ModuleName)
-> LImportDecl GhcPs
-> ModuleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ImportDecl GhcPs -> Located ModuleName
forall pass. ImportDecl pass -> Located ModuleName
ideclName (ImportDecl GhcPs -> Located ModuleName)
-> (LImportDecl GhcPs -> ImportDecl GhcPs)
-> LImportDecl GhcPs
-> Located ModuleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LImportDecl GhcPs -> ImportDecl GhcPs
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc)
[LImportDecl GhcPs]
ord_idecls
implicit_prelude :: Bool
implicit_prelude = Extension -> DynFlags -> Bool
xopt Extension
LangExt.ImplicitPrelude DynFlags
dflags
implicit_imports :: [LImportDecl GhcPs]
implicit_imports = ModuleName
-> SrcSpan -> Bool -> [LImportDecl GhcPs] -> [LImportDecl GhcPs]
mkPrelImports (Located ModuleName -> SrcSpanLess (Located ModuleName)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located ModuleName
mod) SrcSpan
main_loc
Bool
implicit_prelude [LImportDecl GhcPs]
imps
convImport :: a -> (Maybe FastString, Located ModuleName)
convImport (a -> Located (SrcSpanLess a)
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L _ i :: SrcSpanLess a
i) = ((StringLiteral -> FastString)
-> Maybe StringLiteral -> Maybe FastString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap StringLiteral -> FastString
sl_fs (ImportDecl pass -> Maybe StringLiteral
forall pass. ImportDecl pass -> Maybe StringLiteral
ideclPkgQual SrcSpanLess a
ImportDecl pass
i)
, ImportDecl pass -> Located ModuleName
forall pass. ImportDecl pass -> Located ModuleName
ideclName SrcSpanLess a
ImportDecl pass
i)
in
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName)
-> IO
([(Maybe FastString, Located ModuleName)],
[(Maybe FastString, Located ModuleName)], Located ModuleName)
forall (m :: * -> *) a. Monad m => a -> m a
return ((LImportDecl GhcPs -> (Maybe FastString, Located ModuleName))
-> [LImportDecl GhcPs] -> [(Maybe FastString, Located ModuleName)]
forall a b. (a -> b) -> [a] -> [b]
map LImportDecl GhcPs -> (Maybe FastString, Located ModuleName)
forall a pass.
(HasSrcSpan a, SrcSpanLess a ~ ImportDecl pass) =>
a -> (Maybe FastString, Located ModuleName)
convImport [LImportDecl GhcPs]
src_idecls,
(LImportDecl GhcPs -> (Maybe FastString, Located ModuleName))
-> [LImportDecl GhcPs] -> [(Maybe FastString, Located ModuleName)]
forall a b. (a -> b) -> [a] -> [b]
map LImportDecl GhcPs -> (Maybe FastString, Located ModuleName)
forall a pass.
(HasSrcSpan a, SrcSpanLess a ~ ImportDecl pass) =>
a -> (Maybe FastString, Located ModuleName)
convImport ([LImportDecl GhcPs]
implicit_imports [LImportDecl GhcPs] -> [LImportDecl GhcPs] -> [LImportDecl GhcPs]
forall a. [a] -> [a] -> [a]
++ [LImportDecl GhcPs]
ordinary_imps),
Located ModuleName
mod)
mkPrelImports :: ModuleName
-> SrcSpan
-> Bool -> [LImportDecl GhcPs]
-> [LImportDecl GhcPs]
mkPrelImports :: ModuleName
-> SrcSpan -> Bool -> [LImportDecl GhcPs] -> [LImportDecl GhcPs]
mkPrelImports this_mod :: ModuleName
this_mod loc :: SrcSpan
loc implicit_prelude :: Bool
implicit_prelude import_decls :: [LImportDecl GhcPs]
import_decls
| ModuleName
this_mod ModuleName -> ModuleName -> Bool
forall a. Eq a => a -> a -> Bool
== ModuleName
pRELUDE_NAME
Bool -> Bool -> Bool
|| Bool
explicit_prelude_import
Bool -> Bool -> Bool
|| Bool -> Bool
not Bool
implicit_prelude
= []
| Bool
otherwise = [LImportDecl GhcPs
preludeImportDecl]
where
explicit_prelude_import :: Bool
explicit_prelude_import
= [()] -> Bool
forall a. [a] -> Bool
notNull [ () | (LImportDecl GhcPs -> Located (SrcSpanLess (LImportDecl GhcPs))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L _ (ImportDecl { ideclName = mod
, ideclPkgQual = Nothing }))
<- [LImportDecl GhcPs]
import_decls
, Located ModuleName -> SrcSpanLess (Located ModuleName)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located ModuleName
mod ModuleName -> ModuleName -> Bool
forall a. Eq a => a -> a -> Bool
== ModuleName
pRELUDE_NAME ]
preludeImportDecl :: LImportDecl GhcPs
preludeImportDecl :: LImportDecl GhcPs
preludeImportDecl
= SrcSpan -> SrcSpanLess (LImportDecl GhcPs) -> LImportDecl GhcPs
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
loc (SrcSpanLess (LImportDecl GhcPs) -> LImportDecl GhcPs)
-> SrcSpanLess (LImportDecl GhcPs) -> LImportDecl GhcPs
forall a b. (a -> b) -> a -> b
$ ImportDecl :: forall pass.
XCImportDecl pass
-> SourceText
-> Located ModuleName
-> Maybe StringLiteral
-> Bool
-> Bool
-> Bool
-> Bool
-> Maybe (Located ModuleName)
-> Maybe (Bool, Located [LIE pass])
-> ImportDecl pass
ImportDecl { ideclExt :: XCImportDecl GhcPs
ideclExt = XCImportDecl GhcPs
NoExt
noExt,
ideclSourceSrc :: SourceText
ideclSourceSrc = SourceText
NoSourceText,
ideclName :: Located ModuleName
ideclName = SrcSpan -> SrcSpanLess (Located ModuleName) -> Located ModuleName
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
loc ModuleName
SrcSpanLess (Located ModuleName)
pRELUDE_NAME,
ideclPkgQual :: Maybe StringLiteral
ideclPkgQual = Maybe StringLiteral
forall a. Maybe a
Nothing,
ideclSource :: Bool
ideclSource = Bool
False,
ideclSafe :: Bool
ideclSafe = Bool
False,
ideclQualified :: Bool
ideclQualified = Bool
False,
ideclImplicit :: Bool
ideclImplicit = Bool
True,
ideclAs :: Maybe (Located ModuleName)
ideclAs = Maybe (Located ModuleName)
forall a. Maybe a
Nothing,
ideclHiding :: Maybe (Bool, Located [LIE GhcPs])
ideclHiding = Maybe (Bool, Located [LIE GhcPs])
forall a. Maybe a
Nothing }
getOptionsFromFile :: DynFlags
-> FilePath
-> IO [Located String]
getOptionsFromFile :: DynFlags -> FilePath -> IO [Located FilePath]
getOptionsFromFile dflags :: DynFlags
dflags filename :: FilePath
filename
= IO Handle
-> (Handle -> IO ())
-> (Handle -> IO [Located FilePath])
-> IO [Located FilePath]
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
Exception.bracket
(FilePath -> IOMode -> IO Handle
openBinaryFile FilePath
filename IOMode
ReadMode)
(Handle -> IO ()
hClose)
(\handle :: Handle
handle -> do
[Located FilePath]
opts <- ([Located Token] -> [Located FilePath])
-> IO [Located Token] -> IO [Located FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (DynFlags -> [Located Token] -> [Located FilePath]
getOptions' DynFlags
dflags)
(DynFlags -> FilePath -> Handle -> IO [Located Token]
lazyGetToks DynFlags
dflags' FilePath
filename Handle
handle)
[Located FilePath]
-> IO [Located FilePath] -> IO [Located FilePath]
forall a b. [a] -> b -> b
seqList [Located FilePath]
opts (IO [Located FilePath] -> IO [Located FilePath])
-> IO [Located FilePath] -> IO [Located FilePath]
forall a b. (a -> b) -> a -> b
$ [Located FilePath] -> IO [Located FilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return [Located FilePath]
opts)
where
dflags' :: DynFlags
dflags' = DynFlags -> GeneralFlag -> DynFlags
gopt_unset DynFlags
dflags GeneralFlag
Opt_Haddock
blockSize :: Int
blockSize :: Int
blockSize = 1024
lazyGetToks :: DynFlags -> FilePath -> Handle -> IO [Located Token]
lazyGetToks :: DynFlags -> FilePath -> Handle -> IO [Located Token]
lazyGetToks dflags :: DynFlags
dflags filename :: FilePath
filename handle :: Handle
handle = do
StringBuffer
buf <- Handle -> Int -> IO StringBuffer
hGetStringBufferBlock Handle
handle Int
blockSize
IO [Located Token] -> IO [Located Token]
forall a. IO a -> IO a
unsafeInterleaveIO (IO [Located Token] -> IO [Located Token])
-> IO [Located Token] -> IO [Located Token]
forall a b. (a -> b) -> a -> b
$ Handle -> PState -> Bool -> Int -> IO [Located Token]
lazyLexBuf Handle
handle (DynFlags -> StringBuffer -> RealSrcLoc -> PState
pragState DynFlags
dflags StringBuffer
buf RealSrcLoc
loc) Bool
False Int
blockSize
where
loc :: RealSrcLoc
loc = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc (FilePath -> FastString
mkFastString FilePath
filename) 1 1
lazyLexBuf :: Handle -> PState -> Bool -> Int -> IO [Located Token]
lazyLexBuf :: Handle -> PState -> Bool -> Int -> IO [Located Token]
lazyLexBuf handle :: Handle
handle state :: PState
state eof :: Bool
eof size :: Int
size = do
case P (Located Token) -> PState -> ParseResult (Located Token)
forall a. P a -> PState -> ParseResult a
unP (Bool -> (Located Token -> P (Located Token)) -> P (Located Token)
forall a. Bool -> (Located Token -> P a) -> P a
lexer Bool
False Located Token -> P (Located Token)
forall (m :: * -> *) a. Monad m => a -> m a
return) PState
state of
POk state' :: PState
state' t :: Located Token
t -> do
if StringBuffer -> Bool
atEnd (PState -> StringBuffer
buffer PState
state') Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
eof
then Handle -> PState -> Int -> IO [Located Token]
getMore Handle
handle PState
state Int
size
else case Located Token -> SrcSpanLess (Located Token)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located Token
t of
ITeof -> [Located Token] -> IO [Located Token]
forall (m :: * -> *) a. Monad m => a -> m a
return [Located Token
t]
_other :: SrcSpanLess (Located Token)
_other -> do [Located Token]
rest <- Handle -> PState -> Bool -> Int -> IO [Located Token]
lazyLexBuf Handle
handle PState
state' Bool
eof Int
size
[Located Token] -> IO [Located Token]
forall (m :: * -> *) a. Monad m => a -> m a
return (Located Token
t Located Token -> [Located Token] -> [Located Token]
forall a. a -> [a] -> [a]
: [Located Token]
rest)
_ | Bool -> Bool
not Bool
eof -> Handle -> PState -> Int -> IO [Located Token]
getMore Handle
handle PState
state Int
size
| Bool
otherwise -> [Located Token] -> IO [Located Token]
forall (m :: * -> *) a. Monad m => a -> m a
return [SrcSpan -> SrcSpanLess (Located Token) -> Located Token
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL (RealSrcSpan -> SrcSpan
RealSrcSpan (PState -> RealSrcSpan
last_loc PState
state)) SrcSpanLess (Located Token)
Token
ITeof]
getMore :: Handle -> PState -> Int -> IO [Located Token]
getMore :: Handle -> PState -> Int -> IO [Located Token]
getMore handle :: Handle
handle state :: PState
state size :: Int
size = do
let new_size :: Int
new_size = Int
size Int -> Int -> Int
forall a. Num a => a -> a -> a
* 2
StringBuffer
nextbuf <- Handle -> Int -> IO StringBuffer
hGetStringBufferBlock Handle
handle Int
new_size
if (StringBuffer -> Int
len StringBuffer
nextbuf Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 0) then Handle -> PState -> Bool -> Int -> IO [Located Token]
lazyLexBuf Handle
handle PState
state Bool
True Int
new_size else do
StringBuffer
newbuf <- StringBuffer -> StringBuffer -> IO StringBuffer
appendStringBuffers (PState -> StringBuffer
buffer PState
state) StringBuffer
nextbuf
IO [Located Token] -> IO [Located Token]
forall a. IO a -> IO a
unsafeInterleaveIO (IO [Located Token] -> IO [Located Token])
-> IO [Located Token] -> IO [Located Token]
forall a b. (a -> b) -> a -> b
$ Handle -> PState -> Bool -> Int -> IO [Located Token]
lazyLexBuf Handle
handle PState
state{buffer :: StringBuffer
buffer=StringBuffer
newbuf} Bool
False Int
new_size
getToks :: DynFlags -> FilePath -> StringBuffer -> [Located Token]
getToks :: DynFlags -> FilePath -> StringBuffer -> [Located Token]
getToks dflags :: DynFlags
dflags filename :: FilePath
filename buf :: StringBuffer
buf = PState -> [Located Token]
lexAll (DynFlags -> StringBuffer -> RealSrcLoc -> PState
pragState DynFlags
dflags StringBuffer
buf RealSrcLoc
loc)
where
loc :: RealSrcLoc
loc = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc (FilePath -> FastString
mkFastString FilePath
filename) 1 1
lexAll :: PState -> [Located Token]
lexAll state :: PState
state = case P (Located Token) -> PState -> ParseResult (Located Token)
forall a. P a -> PState -> ParseResult a
unP (Bool -> (Located Token -> P (Located Token)) -> P (Located Token)
forall a. Bool -> (Located Token -> P a) -> P a
lexer Bool
False Located Token -> P (Located Token)
forall (m :: * -> *) a. Monad m => a -> m a
return) PState
state of
POk _ t :: Located Token
t@(Located Token -> Located (SrcSpanLess (Located Token))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L _ ITeof) -> [Located Token
t]
POk state' :: PState
state' t :: Located Token
t -> Located Token
t Located Token -> [Located Token] -> [Located Token]
forall a. a -> [a] -> [a]
: PState -> [Located Token]
lexAll PState
state'
_ -> [SrcSpan -> SrcSpanLess (Located Token) -> Located Token
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL (RealSrcSpan -> SrcSpan
RealSrcSpan (PState -> RealSrcSpan
last_loc PState
state)) SrcSpanLess (Located Token)
Token
ITeof]
getOptions :: DynFlags
-> StringBuffer
-> FilePath
-> [Located String]
getOptions :: DynFlags -> StringBuffer -> FilePath -> [Located FilePath]
getOptions dflags :: DynFlags
dflags buf :: StringBuffer
buf filename :: FilePath
filename
= DynFlags -> [Located Token] -> [Located FilePath]
getOptions' DynFlags
dflags (DynFlags -> FilePath -> StringBuffer -> [Located Token]
getToks DynFlags
dflags FilePath
filename StringBuffer
buf)
getOptions' :: DynFlags
-> [Located Token]
-> [Located String]
getOptions' :: DynFlags -> [Located Token] -> [Located FilePath]
getOptions' dflags :: DynFlags
dflags toks :: [Located Token]
toks
= [Located Token] -> [Located FilePath]
parseToks [Located Token]
toks
where
parseToks :: [Located Token] -> [Located FilePath]
parseToks (open :: Located Token
open:close :: Located Token
close:xs :: [Located Token]
xs)
| IToptions_prag str <- Located Token -> SrcSpanLess (Located Token)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located Token
open
, SrcSpanLess (Located Token)
ITclose_prag <- Located Token -> SrcSpanLess (Located Token)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located Token
close
= case FilePath -> Either FilePath [FilePath]
toArgs FilePath
str of
Left _err :: FilePath
_err -> FilePath -> DynFlags -> SrcSpan -> [Located FilePath]
forall a. FilePath -> DynFlags -> SrcSpan -> a
optionsParseError FilePath
str DynFlags
dflags (SrcSpan -> [Located FilePath]) -> SrcSpan -> [Located FilePath]
forall a b. (a -> b) -> a -> b
$
SrcSpan -> SrcSpan -> SrcSpan
combineSrcSpans (Located Token -> SrcSpan
forall a. HasSrcSpan a => a -> SrcSpan
getLoc Located Token
open) (Located Token -> SrcSpan
forall a. HasSrcSpan a => a -> SrcSpan
getLoc Located Token
close)
Right args :: [FilePath]
args -> (FilePath -> Located FilePath) -> [FilePath] -> [Located FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (SrcSpan -> SrcSpanLess (Located FilePath) -> Located FilePath
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL (Located Token -> SrcSpan
forall a. HasSrcSpan a => a -> SrcSpan
getLoc Located Token
open)) [FilePath]
args [Located FilePath] -> [Located FilePath] -> [Located FilePath]
forall a. [a] -> [a] -> [a]
++ [Located Token] -> [Located FilePath]
parseToks [Located Token]
xs
parseToks (open :: Located Token
open:close :: Located Token
close:xs :: [Located Token]
xs)
| ITinclude_prag str <- Located Token -> SrcSpanLess (Located Token)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located Token
open
, SrcSpanLess (Located Token)
ITclose_prag <- Located Token -> SrcSpanLess (Located Token)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located Token
close
= (FilePath -> Located FilePath) -> [FilePath] -> [Located FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (SrcSpan -> SrcSpanLess (Located FilePath) -> Located FilePath
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL (Located Token -> SrcSpan
forall a. HasSrcSpan a => a -> SrcSpan
getLoc Located Token
open)) ["-#include",FilePath -> FilePath
removeSpaces FilePath
str] [Located FilePath] -> [Located FilePath] -> [Located FilePath]
forall a. [a] -> [a] -> [a]
++
[Located Token] -> [Located FilePath]
parseToks [Located Token]
xs
parseToks (open :: Located Token
open:close :: Located Token
close:xs :: [Located Token]
xs)
| ITdocOptions str <- Located Token -> SrcSpanLess (Located Token)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located Token
open
, SrcSpanLess (Located Token)
ITclose_prag <- Located Token -> SrcSpanLess (Located Token)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located Token
close
= (FilePath -> Located FilePath) -> [FilePath] -> [Located FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (SrcSpan -> SrcSpanLess (Located FilePath) -> Located FilePath
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL (Located Token -> SrcSpan
forall a. HasSrcSpan a => a -> SrcSpan
getLoc Located Token
open)) ["-haddock-opts", FilePath -> FilePath
removeSpaces FilePath
str]
[Located FilePath] -> [Located FilePath] -> [Located FilePath]
forall a. [a] -> [a] -> [a]
++ [Located Token] -> [Located FilePath]
parseToks [Located Token]
xs
parseToks (open :: Located Token
open:xs :: [Located Token]
xs)
| SrcSpanLess (Located Token)
ITlanguage_prag <- Located Token -> SrcSpanLess (Located Token)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located Token
open
= [Located Token] -> [Located FilePath]
parseLanguage [Located Token]
xs
parseToks (comment :: Located Token
comment:xs :: [Located Token]
xs)
| Token -> Bool
isComment (Located Token -> SrcSpanLess (Located Token)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located Token
comment)
= [Located Token] -> [Located FilePath]
parseToks [Located Token]
xs
parseToks _ = []
parseLanguage :: [Located Token] -> [Located FilePath]
parseLanguage ((Located Token -> Located (SrcSpanLess (Located Token))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L loc :: SrcSpan
loc (ITconid fs)):rest :: [Located Token]
rest)
= DynFlags -> Located FastString -> Located FilePath
checkExtension DynFlags
dflags (SrcSpan -> SrcSpanLess (Located FastString) -> Located FastString
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
loc FastString
SrcSpanLess (Located FastString)
fs) Located FilePath -> [Located FilePath] -> [Located FilePath]
forall a. a -> [a] -> [a]
:
case [Located Token]
rest of
(Located Token -> Located (SrcSpanLess (Located Token))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L _loc :: SrcSpan
_loc ITcomma):more :: [Located Token]
more -> [Located Token] -> [Located FilePath]
parseLanguage [Located Token]
more
(Located Token -> Located (SrcSpanLess (Located Token))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L _loc :: SrcSpan
_loc ITclose_prag):more :: [Located Token]
more -> [Located Token] -> [Located FilePath]
parseToks [Located Token]
more
(Located Token -> Located (SrcSpanLess (Located Token))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L loc :: SrcSpan
loc _):_ -> DynFlags -> SrcSpan -> [Located FilePath]
forall a. DynFlags -> SrcSpan -> a
languagePragParseError DynFlags
dflags SrcSpan
loc
[] -> FilePath -> [Located FilePath]
forall a. FilePath -> a
panic "getOptions'.parseLanguage(1) went past eof token"
parseLanguage (tok :: Located Token
tok:_)
= DynFlags -> SrcSpan -> [Located FilePath]
forall a. DynFlags -> SrcSpan -> a
languagePragParseError DynFlags
dflags (Located Token -> SrcSpan
forall a. HasSrcSpan a => a -> SrcSpan
getLoc Located Token
tok)
parseLanguage []
= FilePath -> [Located FilePath]
forall a. FilePath -> a
panic "getOptions'.parseLanguage(2) went past eof token"
isComment :: Token -> Bool
isComment :: Token -> Bool
isComment c :: Token
c =
case Token
c of
(ITlineComment {}) -> Bool
True
(ITblockComment {}) -> Bool
True
(ITdocCommentNext {}) -> Bool
True
(ITdocCommentPrev {}) -> Bool
True
(ITdocCommentNamed {}) -> Bool
True
(ITdocSection {}) -> Bool
True
_ -> Bool
False
checkProcessArgsResult :: MonadIO m => DynFlags -> [Located String] -> m ()
checkProcessArgsResult :: DynFlags -> [Located FilePath] -> m ()
checkProcessArgsResult dflags :: DynFlags
dflags flags :: [Located FilePath]
flags
= Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([Located FilePath] -> Bool
forall a. [a] -> Bool
notNull [Located FilePath]
flags) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ SourceError -> IO ()
forall e a. Exception e => e -> IO a
throwIO (SourceError -> IO ()) -> SourceError -> IO ()
forall a b. (a -> b) -> a -> b
$ ErrorMessages -> SourceError
mkSrcErr (ErrorMessages -> SourceError) -> ErrorMessages -> SourceError
forall a b. (a -> b) -> a -> b
$ [ErrMsg] -> ErrorMessages
forall a. [a] -> Bag a
listToBag ([ErrMsg] -> ErrorMessages) -> [ErrMsg] -> ErrorMessages
forall a b. (a -> b) -> a -> b
$ (Located FilePath -> ErrMsg) -> [Located FilePath] -> [ErrMsg]
forall a b. (a -> b) -> [a] -> [b]
map Located FilePath -> ErrMsg
mkMsg [Located FilePath]
flags
where mkMsg :: Located FilePath -> ErrMsg
mkMsg (Located FilePath -> Located (SrcSpanLess (Located FilePath))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L loc :: SrcSpan
loc flag :: SrcSpanLess (Located FilePath)
flag)
= DynFlags -> SrcSpan -> MsgDoc -> ErrMsg
mkPlainErrMsg DynFlags
dflags SrcSpan
loc (MsgDoc -> ErrMsg) -> MsgDoc -> ErrMsg
forall a b. (a -> b) -> a -> b
$
(FilePath -> MsgDoc
text "unknown flag in {-# OPTIONS_GHC #-} pragma:" MsgDoc -> MsgDoc -> MsgDoc
<+>
FilePath -> MsgDoc
text FilePath
SrcSpanLess (Located FilePath)
flag)
checkExtension :: DynFlags -> Located FastString -> Located String
checkExtension :: DynFlags -> Located FastString -> Located FilePath
checkExtension dflags :: DynFlags
dflags (Located FastString -> Located (SrcSpanLess (Located FastString))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L l :: SrcSpan
l ext :: SrcSpanLess (Located FastString)
ext)
= let ext' :: FilePath
ext' = FastString -> FilePath
unpackFS FastString
SrcSpanLess (Located FastString)
ext in
if FilePath
ext' FilePath -> [FilePath] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [FilePath]
supportedLanguagesAndExtensions
then SrcSpan -> SrcSpanLess (Located FilePath) -> Located FilePath
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
l ("-X"FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++FilePath
ext')
else DynFlags -> SrcSpan -> FilePath -> Located FilePath
forall a. DynFlags -> SrcSpan -> FilePath -> a
unsupportedExtnError DynFlags
dflags SrcSpan
l FilePath
ext'
languagePragParseError :: DynFlags -> SrcSpan -> a
languagePragParseError :: DynFlags -> SrcSpan -> a
languagePragParseError dflags :: DynFlags
dflags loc :: SrcSpan
loc =
DynFlags -> SrcSpan -> MsgDoc -> a
forall a. DynFlags -> SrcSpan -> MsgDoc -> a
throwErr DynFlags
dflags SrcSpan
loc (MsgDoc -> a) -> MsgDoc -> a
forall a b. (a -> b) -> a -> b
$
[MsgDoc] -> MsgDoc
vcat [ FilePath -> MsgDoc
text "Cannot parse LANGUAGE pragma"
, FilePath -> MsgDoc
text "Expecting comma-separated list of language options,"
, FilePath -> MsgDoc
text "each starting with a capital letter"
, Int -> MsgDoc -> MsgDoc
nest 2 (FilePath -> MsgDoc
text "E.g. {-# LANGUAGE TemplateHaskell, GADTs #-}") ]
unsupportedExtnError :: DynFlags -> SrcSpan -> String -> a
unsupportedExtnError :: DynFlags -> SrcSpan -> FilePath -> a
unsupportedExtnError dflags :: DynFlags
dflags loc :: SrcSpan
loc unsup :: FilePath
unsup =
DynFlags -> SrcSpan -> MsgDoc -> a
forall a. DynFlags -> SrcSpan -> MsgDoc -> a
throwErr DynFlags
dflags SrcSpan
loc (MsgDoc -> a) -> MsgDoc -> a
forall a b. (a -> b) -> a -> b
$
FilePath -> MsgDoc
text "Unsupported extension: " MsgDoc -> MsgDoc -> MsgDoc
<> FilePath -> MsgDoc
text FilePath
unsup MsgDoc -> MsgDoc -> MsgDoc
$$
if [FilePath] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
suggestions then MsgDoc
Outputable.empty else FilePath -> MsgDoc
text "Perhaps you meant" MsgDoc -> MsgDoc -> MsgDoc
<+> [MsgDoc] -> MsgDoc
quotedListWithOr ((FilePath -> MsgDoc) -> [FilePath] -> [MsgDoc]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> MsgDoc
text [FilePath]
suggestions)
where
suggestions :: [FilePath]
suggestions = FilePath -> [FilePath] -> [FilePath]
fuzzyMatch FilePath
unsup [FilePath]
supportedLanguagesAndExtensions
optionsErrorMsgs :: DynFlags -> [String] -> [Located String] -> FilePath -> Messages
optionsErrorMsgs :: DynFlags
-> [FilePath]
-> [Located FilePath]
-> FilePath
-> (ErrorMessages, ErrorMessages)
optionsErrorMsgs dflags :: DynFlags
dflags unhandled_flags :: [FilePath]
unhandled_flags flags_lines :: [Located FilePath]
flags_lines _filename :: FilePath
_filename
= (ErrorMessages
forall a. Bag a
emptyBag, [ErrMsg] -> ErrorMessages
forall a. [a] -> Bag a
listToBag ((Located FilePath -> ErrMsg) -> [Located FilePath] -> [ErrMsg]
forall a b. (a -> b) -> [a] -> [b]
map Located FilePath -> ErrMsg
mkMsg [Located FilePath]
unhandled_flags_lines))
where unhandled_flags_lines :: [Located String]
unhandled_flags_lines :: [Located FilePath]
unhandled_flags_lines = [ SrcSpan -> SrcSpanLess (Located FilePath) -> Located FilePath
forall a. HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
cL SrcSpan
l FilePath
SrcSpanLess (Located FilePath)
f
| FilePath
f <- [FilePath]
unhandled_flags
, (Located FilePath -> Located (SrcSpanLess (Located FilePath))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L l :: SrcSpan
l f' :: SrcSpanLess (Located FilePath)
f') <- [Located FilePath]
flags_lines
, FilePath
f FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
SrcSpanLess (Located FilePath)
f' ]
mkMsg :: Located FilePath -> ErrMsg
mkMsg (Located FilePath -> Located (SrcSpanLess (Located FilePath))
forall a. HasSrcSpan a => a -> Located (SrcSpanLess a)
dL->L flagSpan :: SrcSpan
flagSpan flag :: SrcSpanLess (Located FilePath)
flag) =
DynFlags -> SrcSpan -> MsgDoc -> ErrMsg
ErrUtils.mkPlainErrMsg DynFlags
dflags SrcSpan
flagSpan (MsgDoc -> ErrMsg) -> MsgDoc -> ErrMsg
forall a b. (a -> b) -> a -> b
$
FilePath -> MsgDoc
text "unknown flag in {-# OPTIONS_GHC #-} pragma:" MsgDoc -> MsgDoc -> MsgDoc
<+> FilePath -> MsgDoc
text FilePath
SrcSpanLess (Located FilePath)
flag
optionsParseError :: String -> DynFlags -> SrcSpan -> a
optionsParseError :: FilePath -> DynFlags -> SrcSpan -> a
optionsParseError str :: FilePath
str dflags :: DynFlags
dflags loc :: SrcSpan
loc =
DynFlags -> SrcSpan -> MsgDoc -> a
forall a. DynFlags -> SrcSpan -> MsgDoc -> a
throwErr DynFlags
dflags SrcSpan
loc (MsgDoc -> a) -> MsgDoc -> a
forall a b. (a -> b) -> a -> b
$
[MsgDoc] -> MsgDoc
vcat [ FilePath -> MsgDoc
text "Error while parsing OPTIONS_GHC pragma."
, FilePath -> MsgDoc
text "Expecting whitespace-separated list of GHC options."
, FilePath -> MsgDoc
text " E.g. {-# OPTIONS_GHC -Wall -O2 #-}"
, FilePath -> MsgDoc
text ("Input was: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> FilePath
forall a. Show a => a -> FilePath
show FilePath
str) ]
throwErr :: DynFlags -> SrcSpan -> SDoc -> a
throwErr :: DynFlags -> SrcSpan -> MsgDoc -> a
throwErr dflags :: DynFlags
dflags loc :: SrcSpan
loc doc :: MsgDoc
doc =
SourceError -> a
forall a e. Exception e => e -> a
throw (SourceError -> a) -> SourceError -> a
forall a b. (a -> b) -> a -> b
$ ErrorMessages -> SourceError
mkSrcErr (ErrorMessages -> SourceError) -> ErrorMessages -> SourceError
forall a b. (a -> b) -> a -> b
$ ErrMsg -> ErrorMessages
forall a. a -> Bag a
unitBag (ErrMsg -> ErrorMessages) -> ErrMsg -> ErrorMessages
forall a b. (a -> b) -> a -> b
$ DynFlags -> SrcSpan -> MsgDoc -> ErrMsg
mkPlainErrMsg DynFlags
dflags SrcSpan
loc MsgDoc
doc