ghc-mod/Types.hs

109 lines
3.1 KiB
Haskell
Raw Normal View History

2012-02-14 02:33:27 +00:00
{-# LANGUAGE FlexibleInstances #-}
2010-04-30 09:36:31 +00:00
module Types where
2010-11-12 07:27:50 +00:00
import Control.Monad
2011-08-24 06:58:12 +00:00
import CoreMonad
2010-11-12 07:27:50 +00:00
import DynFlags
2011-08-24 07:50:26 +00:00
import ErrMsg
2010-04-30 09:36:31 +00:00
import Exception
import GHC
import GHC.Paths (libdir)
2010-11-12 07:27:50 +00:00
----------------------------------------------------------------
data OutputStyle = LispStyle | PlainStyle
2012-02-14 01:21:48 +00:00
2010-04-30 09:36:31 +00:00
data Options = Options {
outputStyle :: OutputStyle
2012-02-14 01:21:48 +00:00
, hlintOpts :: [String]
, ghcOpts :: [String]
, operators :: Bool
2010-04-30 09:36:31 +00:00
}
2012-02-14 02:33:27 +00:00
----------------------------------------------------------------
convert :: ToString a => Options -> a -> String
convert Options{ outputStyle = LispStyle } = toLisp
convert Options{ outputStyle = PlainStyle } = toPlain
class ToString a where
toLisp :: a -> String
toPlain :: a -> String
instance ToString [String] where
toLisp = addNewLine . toSexp True
toPlain = unlines
instance ToString [((Int,Int,Int,Int),String)] where
toLisp = addNewLine . toSexp False . map toS
where
toS x = "(" ++ tupToString x ++ ")"
toPlain = unlines . map tupToString
toSexp :: Bool -> [String] -> String
toSexp False ss = "(" ++ unwords ss ++ ")"
toSexp True ss = "(" ++ unwords (map quote ss) ++ ")"
tupToString :: ((Int,Int,Int,Int),String) -> String
tupToString ((a,b,c,d),s) = show a ++ " "
++ show b ++ " "
++ show c ++ " "
++ show d ++ " "
++ quote s
quote :: String -> String
quote x = "\"" ++ x ++ "\""
addNewLine :: String -> String
addNewLine = (++ "\n")
2012-02-14 01:21:48 +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) . setGhcFlags opt
2010-11-12 07:27:50 +00:00
2011-10-18 03:22:48 +00:00
initSession :: Options -> [String] -> [FilePath] -> Bool -> Ghc LogReader
initSession opt cmdOpts idirs logging = do
2010-11-12 07:27:50 +00:00
dflags <- getSessionDynFlags
let opts = map noLoc cmdOpts
(dflags',_,_) <- parseDynamicFlags dflags opts
(dflags'',readLog) <- liftIO . (>>= setLogger logging) . setGhcFlags opt . setFlags dflags' $ idirs
2011-08-24 06:58:12 +00:00
setSessionDynFlags dflags''
return readLog
2010-11-12 07:27:50 +00:00
----------------------------------------------------------------
2011-10-18 03:22:48 +00:00
setFlags :: DynFlags -> [FilePath] -> DynFlags
setFlags d idirs = d'
2011-05-24 07:00:47 +00:00
where
d' = d {
packageFlags = ghcPackage : packageFlags d
2011-10-18 03:22:48 +00:00
, importPaths = idirs
2011-05-24 07:00:47 +00:00
, ghcLink = NoLink
, hscTarget = HscInterpreted
}
2010-11-12 07:27:50 +00:00
ghcPackage :: PackageFlag
ghcPackage = ExposePackage "ghc"
setGhcFlags :: Monad m => Options -> DynFlags -> m DynFlags
setGhcFlags opt flagset =
do (flagset',_,_) <- parseDynamicFlags flagset (map noLoc (ghcOpts opt))
return flagset'
2011-08-24 06:58:12 +00:00
----------------------------------------------------------------
2010-11-12 07:27:50 +00:00
setTargetFile :: (GhcMonad m) => String -> m ()
setTargetFile file = do
target <- guessTarget file Nothing
setTargets [target]