ghc-mod/Types.hs

121 lines
3.4 KiB
Haskell
Raw Normal View History

2011-08-24 06:58:12 +00:00
{-# LANGUAGE CPP #-}
2010-04-30 09:36:31 +00:00
module Types where
2011-08-24 06:58:12 +00:00
import Control.Applicative
2010-11-12 07:27:50 +00:00
import Control.Monad
2011-08-24 06:58:12 +00:00
import CoreMonad
import Data.IORef
2010-11-12 07:27:50 +00:00
import DynFlags
2011-08-24 06:58:12 +00:00
import ErrUtils
2010-04-30 09:36:31 +00:00
import Exception
2011-08-24 06:58:12 +00:00
import FastString
2010-04-30 09:36:31 +00:00
import GHC
import GHC.Paths (libdir)
2011-08-24 06:58:12 +00:00
import Outputable
import System.FilePath
import Pretty
2010-04-30 09:36:31 +00:00
2010-11-12 07:27:50 +00:00
----------------------------------------------------------------
2010-04-30 09:36:31 +00:00
data Options = Options {
convert :: [String] -> String
, hlintOpts :: [String]
2011-08-02 18:18:07 +00:00
, checkIncludes :: [String]
2011-01-27 05:29:39 +00:00
, operators :: Bool
, packageConfs :: [FilePath]
, useUserPackageConf :: Bool
2010-04-30 09:36:31 +00:00
}
2010-11-12 07:27:50 +00:00
withGHC :: (MonadPlus m) => Ghc (m a) -> IO (m a)
2010-04-30 09:36:31 +00:00
withGHC body = ghandle ignore $ runGhc (Just libdir) body
where
2010-11-12 07:27:50 +00:00
ignore :: (MonadPlus m) => SomeException -> IO (m a)
ignore _ = return mzero
----------------------------------------------------------------
2010-04-30 09:36:31 +00:00
initSession0 :: Options -> Ghc [PackageId]
initSession0 opt = getSessionDynFlags >>=
setSessionDynFlags . setPackageConfFlags opt
2010-11-12 07:27:50 +00:00
2011-08-24 06:58:12 +00:00
initSession :: Options -> [String] -> Maybe [FilePath] -> Bool -> Ghc LogReader
initSession opt cmdOpts midirs logging = do
2010-11-12 07:27:50 +00:00
dflags <- getSessionDynFlags
let opts = map noLoc cmdOpts
(dflags',_,_) <- parseDynamicFlags dflags opts
2011-08-24 06:58:12 +00:00
(dflags'',readLog) <- liftIO . setLogger logging . setPackageConfFlags opt . setFlags dflags' $ midirs
setSessionDynFlags dflags''
return readLog
2010-11-12 07:27:50 +00:00
----------------------------------------------------------------
2011-05-24 07:00:47 +00:00
setFlags :: DynFlags -> Maybe [FilePath] -> DynFlags
setFlags d midirs = maybe d' (\x -> d' { importPaths = x }) midirs
where
d' = d {
packageFlags = ghcPackage : packageFlags d
, ghcLink = NoLink
, hscTarget = HscInterpreted
}
2010-11-12 07:27:50 +00:00
ghcPackage :: PackageFlag
ghcPackage = ExposePackage "ghc"
setPackageConfFlags :: Options -> DynFlags -> DynFlags
setPackageConfFlags
Options { packageConfs = confs, useUserPackageConf = useUser }
flagset@DynFlags { extraPkgConfs = extra, flags = origFlags }
= flagset { extraPkgConfs = extra', flags = flags' }
where
extra' = confs ++ extra
2011-08-24 06:58:12 +00:00
flags' = if useUser then
origFlags
else
filter (/=Opt_ReadUserPackageConf) origFlags
----------------------------------------------------------------
type LogReader = IO [String]
setLogger :: Bool -> DynFlags -> IO (DynFlags, LogReader)
setLogger False df = return (newdf, undefined)
where
newdf = df { log_action = \_ _ _ _ -> return () }
setLogger True df = do
ref <- newIORef [] :: IO (IORef [String])
let newdf = df { log_action = appendLog ref }
return (newdf, reverse <$> readIORef ref)
where
appendLog ref _ src _ msg = modifyIORef ref (\ls -> ppMsg src msg : ls)
ppMsg :: SrcSpan -> Message -> String
#if __GLASGOW_HASKELL__ >= 702
ppMsg (UnhelpfulSpan _) _ = undefined
ppMsg (RealSrcSpan src) msg
#else
ppMsg src msg
#endif
= file ++ ":" ++ line ++ ":" ++ col ++ ":" ++ cts ++ "\0" -- xxx
where
file = takeFileName $ unpackFS (srcSpanFile src)
line = show (srcSpanStartLine src)
col = show (srcSpanStartCol src)
cts = showMsg msg
style :: PprStyle
style = mkUserStyle neverQualify AllTheWay
showMsg :: SDoc -> String
showMsg d = map toNull . Pretty.showDocWith PageMode $ d style
where
toNull '\n' = '\0'
toNull x = x
2010-11-12 07:27:50 +00:00
----------------------------------------------------------------
setTargetFile :: (GhcMonad m) => String -> m ()
setTargetFile file = do
target <- guessTarget file Nothing
setTargets [target]