ghc-mod/Gap.hs

211 lines
5.1 KiB
Haskell
Raw Normal View History

2012-02-14 07:09:53 +00:00
{-# LANGUAGE CPP #-}
module Gap (
Gap.ClsInst
, mkTarget
, showDocForUser
, showDoc
, styleDoc
, setLogAction
, supportedExtensions
2012-02-14 07:09:53 +00:00
, getSrcSpan
, getSrcFile
, renderMsg
, setCtx
, fOptions
, toStringBuffer
, liftIO
, showSeverityCaption
2012-02-14 07:09:53 +00:00
#if __GLASGOW_HASKELL__ >= 702
#else
, module Pretty
#endif
) where
import Control.Applicative hiding (empty)
import Control.Monad
import Data.Time.Clock
2012-02-14 07:09:53 +00:00
import DynFlags
import ErrUtils
2012-02-14 07:09:53 +00:00
import FastString
import GHC
2012-02-16 05:44:20 +00:00
import GHCChoice
2012-02-14 07:09:53 +00:00
import Outputable
import StringBuffer
import qualified InstEnv
import qualified Pretty
import qualified StringBuffer as SB
2012-02-14 07:09:53 +00:00
#if __GLASGOW_HASKELL__ >= 702
import CoreMonad (liftIO)
#else
import HscTypes (liftIO)
import Pretty
#endif
#if __GLASGOW_HASKELL__ < 706
import Control.Arrow
import Data.Convertible
#endif
2012-02-15 04:58:04 +00:00
{-
pretty :: Outputable a => a -> String
pretty = showSDocForUser neverQualify . ppr
debug :: Outputable a => a -> b -> b
debug x v = trace (pretty x) v
-}
----------------------------------------------------------------
----------------------------------------------------------------
--
#if __GLASGOW_HASKELL__ >= 706
type ClsInst = InstEnv.ClsInst
#else
type ClsInst = InstEnv.Instance
#endif
mkTarget :: TargetId -> Bool -> Maybe (SB.StringBuffer, UTCTime) -> Target
#if __GLASGOW_HASKELL__ >= 706
mkTarget = Target
#else
mkTarget tid allowObjCode = Target tid allowObjCode . (fmap . second) convert
#endif
----------------------------------------------------------------
----------------------------------------------------------------
showDocForUser :: PrintUnqualified -> SDoc -> String
#if __GLASGOW_HASKELL__ >= 706
showDocForUser = showSDocForUser tracingDynFlags
#else
showDocForUser = showSDocForUser
#endif
showDoc :: SDoc -> String
#if __GLASGOW_HASKELL__ >= 706
showDoc = showSDoc tracingDynFlags
#else
showDoc = showSDoc
#endif
styleDoc :: PprStyle -> SDoc -> Pretty.Doc
#if __GLASGOW_HASKELL__ >= 706
styleDoc = withPprStyleDoc tracingDynFlags
#else
styleDoc = withPprStyleDoc
#endif
setLogAction :: DynFlags
-> (DynFlags -> Severity -> SrcSpan -> PprStyle -> SDoc -> IO ())
-> DynFlags
setLogAction df f =
#if __GLASGOW_HASKELL__ >= 706
df { log_action = f }
#else
df { log_action = f df }
#endif
2012-02-14 07:09:53 +00:00
----------------------------------------------------------------
----------------------------------------------------------------
supportedExtensions :: [String]
#if __GLASGOW_HASKELL__ >= 700
supportedExtensions = supportedLanguagesAndExtensions
#else
supportedExtensions = supportedLanguages
#endif
----------------------------------------------------------------
----------------------------------------------------------------
getSrcSpan :: SrcSpan -> Maybe (Int,Int,Int,Int)
#if __GLASGOW_HASKELL__ >= 702
getSrcSpan (RealSrcSpan spn)
#else
getSrcSpan spn | isGoodSrcSpan spn
#endif
= Just (srcSpanStartLine spn
, srcSpanStartCol spn
, srcSpanEndLine spn
, srcSpanEndCol spn)
getSrcSpan _ = Nothing
getSrcFile :: SrcSpan -> Maybe String
#if __GLASGOW_HASKELL__ >= 702
getSrcFile (RealSrcSpan spn) = Just . unpackFS . srcSpanFile $ spn
#else
getSrcFile spn | isGoodSrcSpan spn = Just . unpackFS . srcSpanFile $ spn
#endif
getSrcFile _ = Nothing
----------------------------------------------------------------
renderMsg :: SDoc -> PprStyle -> String
#if __GLASGOW_HASKELL__ >= 706
renderMsg d stl = renderWithStyle tracingDynFlags d stl
#elif __GLASGOW_HASKELL__ >= 702
renderMsg d stl = renderWithStyle d stl
2012-02-14 07:09:53 +00:00
#else
renderMsg d stl = Pretty.showDocWith PageMode $ d stl
#endif
----------------------------------------------------------------
toStringBuffer :: [String] -> Ghc StringBuffer
#if __GLASGOW_HASKELL__ >= 702
toStringBuffer = return . stringToStringBuffer . unlines
#else
toStringBuffer = liftIO . stringToStringBuffer . unlines
#endif
----------------------------------------------------------------
fOptions :: [String]
2012-06-07 06:56:55 +00:00
#if __GLASGOW_HASKELL__ >= 704
fOptions = [option | (option,_,_) <- fFlags]
++ [option | (option,_,_) <- fWarningFlags]
++ [option | (option,_,_) <- fLangFlags]
#elif __GLASGOW_HASKELL__ == 702
2012-02-14 07:09:53 +00:00
fOptions = [option | (option,_,_,_) <- fFlags]
#else
fOptions = [option | (option,_,_) <- fFlags]
#endif
----------------------------------------------------------------
----------------------------------------------------------------
setCtx :: [ModSummary] -> Ghc Bool
#if __GLASGOW_HASKELL__ >= 704
2012-02-14 07:09:53 +00:00
setCtx ms = do
#if __GLASGOW_HASKELL__ >= 706
let modName = IIModule . moduleName . ms_mod
#else
let modName = IIModule . ms_mod
#endif
top <- map modName <$> filterM isTop ms
2012-02-14 07:09:53 +00:00
setContext top
return (not . null $ top)
#else
setCtx ms = do
top <- map ms_mod <$> filterM isTop ms
setContext top []
2012-02-14 07:09:53 +00:00
return (not . null $ top)
#endif
where
2012-02-16 05:44:20 +00:00
isTop mos = lookupMod ||> returnFalse
2012-02-14 07:09:53 +00:00
where
lookupMod = lookupModule (ms_mod_name mos) Nothing >> return True
2012-02-15 05:52:48 +00:00
returnFalse = return False
showSeverityCaption :: Severity -> String
#if __GLASGOW_HASKELL__ >= 706
showSeverityCaption SevWarning = "Warning:"
showSeverityCaption _ = ""
#else
showSeverityCaption = const ""
#endif