Gap.hs 5.1 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211
  1. {-# LANGUAGE CPP #-}
  2. module Gap (
  3. Gap.ClsInst
  4. , mkTarget
  5. , showDocForUser
  6. , showDoc
  7. , styleDoc
  8. , setLogAction
  9. , supportedExtensions
  10. , getSrcSpan
  11. , getSrcFile
  12. , renderMsg
  13. , setCtx
  14. , fOptions
  15. , toStringBuffer
  16. , liftIO
  17. , showSeverityCaption
  18. #if __GLASGOW_HASKELL__ >= 702
  19. #else
  20. , module Pretty
  21. #endif
  22. ) where
  23. import Control.Applicative hiding (empty)
  24. import Control.Monad
  25. import Data.Time.Clock
  26. import DynFlags
  27. import ErrUtils
  28. import FastString
  29. import GHC
  30. import GHCChoice
  31. import Outputable
  32. import StringBuffer
  33. import qualified InstEnv
  34. import qualified Pretty
  35. import qualified StringBuffer as SB
  36. #if __GLASGOW_HASKELL__ >= 702
  37. import CoreMonad (liftIO)
  38. #else
  39. import HscTypes (liftIO)
  40. import Pretty
  41. #endif
  42. #if __GLASGOW_HASKELL__ < 706
  43. import Control.Arrow
  44. import Data.Convertible
  45. #endif
  46. {-
  47. pretty :: Outputable a => a -> String
  48. pretty = showSDocForUser neverQualify . ppr
  49. debug :: Outputable a => a -> b -> b
  50. debug x v = trace (pretty x) v
  51. -}
  52. ----------------------------------------------------------------
  53. ----------------------------------------------------------------
  54. --
  55. #if __GLASGOW_HASKELL__ >= 706
  56. type ClsInst = InstEnv.ClsInst
  57. #else
  58. type ClsInst = InstEnv.Instance
  59. #endif
  60. mkTarget :: TargetId -> Bool -> Maybe (SB.StringBuffer, UTCTime) -> Target
  61. #if __GLASGOW_HASKELL__ >= 706
  62. mkTarget = Target
  63. #else
  64. mkTarget tid allowObjCode = Target tid allowObjCode . (fmap . second) convert
  65. #endif
  66. ----------------------------------------------------------------
  67. ----------------------------------------------------------------
  68. showDocForUser :: PrintUnqualified -> SDoc -> String
  69. #if __GLASGOW_HASKELL__ >= 706
  70. showDocForUser = showSDocForUser tracingDynFlags
  71. #else
  72. showDocForUser = showSDocForUser
  73. #endif
  74. showDoc :: SDoc -> String
  75. #if __GLASGOW_HASKELL__ >= 706
  76. showDoc = showSDoc tracingDynFlags
  77. #else
  78. showDoc = showSDoc
  79. #endif
  80. styleDoc :: PprStyle -> SDoc -> Pretty.Doc
  81. #if __GLASGOW_HASKELL__ >= 706
  82. styleDoc = withPprStyleDoc tracingDynFlags
  83. #else
  84. styleDoc = withPprStyleDoc
  85. #endif
  86. setLogAction :: DynFlags
  87. -> (DynFlags -> Severity -> SrcSpan -> PprStyle -> SDoc -> IO ())
  88. -> DynFlags
  89. setLogAction df f =
  90. #if __GLASGOW_HASKELL__ >= 706
  91. df { log_action = f }
  92. #else
  93. df { log_action = f df }
  94. #endif
  95. ----------------------------------------------------------------
  96. ----------------------------------------------------------------
  97. supportedExtensions :: [String]
  98. #if __GLASGOW_HASKELL__ >= 700
  99. supportedExtensions = supportedLanguagesAndExtensions
  100. #else
  101. supportedExtensions = supportedLanguages
  102. #endif
  103. ----------------------------------------------------------------
  104. ----------------------------------------------------------------
  105. getSrcSpan :: SrcSpan -> Maybe (Int,Int,Int,Int)
  106. #if __GLASGOW_HASKELL__ >= 702
  107. getSrcSpan (RealSrcSpan spn)
  108. #else
  109. getSrcSpan spn | isGoodSrcSpan spn
  110. #endif
  111. = Just (srcSpanStartLine spn
  112. , srcSpanStartCol spn
  113. , srcSpanEndLine spn
  114. , srcSpanEndCol spn)
  115. getSrcSpan _ = Nothing
  116. getSrcFile :: SrcSpan -> Maybe String
  117. #if __GLASGOW_HASKELL__ >= 702
  118. getSrcFile (RealSrcSpan spn) = Just . unpackFS . srcSpanFile $ spn
  119. #else
  120. getSrcFile spn | isGoodSrcSpan spn = Just . unpackFS . srcSpanFile $ spn
  121. #endif
  122. getSrcFile _ = Nothing
  123. ----------------------------------------------------------------
  124. renderMsg :: SDoc -> PprStyle -> String
  125. #if __GLASGOW_HASKELL__ >= 706
  126. renderMsg d stl = renderWithStyle tracingDynFlags d stl
  127. #elif __GLASGOW_HASKELL__ >= 702
  128. renderMsg d stl = renderWithStyle d stl
  129. #else
  130. renderMsg d stl = Pretty.showDocWith PageMode $ d stl
  131. #endif
  132. ----------------------------------------------------------------
  133. toStringBuffer :: [String] -> Ghc StringBuffer
  134. #if __GLASGOW_HASKELL__ >= 702
  135. toStringBuffer = return . stringToStringBuffer . unlines
  136. #else
  137. toStringBuffer = liftIO . stringToStringBuffer . unlines
  138. #endif
  139. ----------------------------------------------------------------
  140. fOptions :: [String]
  141. #if __GLASGOW_HASKELL__ >= 704
  142. fOptions = [option | (option,_,_) <- fFlags]
  143. ++ [option | (option,_,_) <- fWarningFlags]
  144. ++ [option | (option,_,_) <- fLangFlags]
  145. #elif __GLASGOW_HASKELL__ == 702
  146. fOptions = [option | (option,_,_,_) <- fFlags]
  147. #else
  148. fOptions = [option | (option,_,_) <- fFlags]
  149. #endif
  150. ----------------------------------------------------------------
  151. ----------------------------------------------------------------
  152. setCtx :: [ModSummary] -> Ghc Bool
  153. #if __GLASGOW_HASKELL__ >= 704
  154. setCtx ms = do
  155. #if __GLASGOW_HASKELL__ >= 706
  156. let modName = IIModule . moduleName . ms_mod
  157. #else
  158. let modName = IIModule . ms_mod
  159. #endif
  160. top <- map modName <$> filterM isTop ms
  161. setContext top
  162. return (not . null $ top)
  163. #else
  164. setCtx ms = do
  165. top <- map ms_mod <$> filterM isTop ms
  166. setContext top []
  167. return (not . null $ top)
  168. #endif
  169. where
  170. isTop mos = lookupMod ||> returnFalse
  171. where
  172. lookupMod = lookupModule (ms_mod_name mos) Nothing >> return True
  173. returnFalse = return False
  174. showSeverityCaption :: Severity -> String
  175. #if __GLASGOW_HASKELL__ >= 706
  176. showSeverityCaption SevWarning = "Warning: "
  177. showSeverityCaption _ = ""
  178. #else
  179. showSeverityCaption = const ""
  180. #endif