Info.hs 6.0 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171
  1. {-# LANGUAGE TupleSections, FlexibleInstances, TypeSynonymInstances #-}
  2. {-# LANGUAGE Rank2Types #-}
  3. module Info (infoExpr, typeExpr) where
  4. import Cabal
  5. import Control.Applicative
  6. import CoreUtils
  7. import Data.Function
  8. import Data.Generics
  9. import Data.List
  10. import Data.Maybe
  11. import Data.Ord as O
  12. import Data.Time.Clock
  13. import Desugar
  14. import GHC
  15. import GHC.SYB.Utils
  16. import GHCApi
  17. import GHCChoice
  18. import qualified Gap
  19. import HscTypes
  20. import NameSet
  21. import Outputable
  22. import PprTyThing
  23. import Pretty (showDocWith, Mode(OneLineMode))
  24. import TcRnTypes
  25. import TcHsSyn (hsPatType)
  26. import Types
  27. ----------------------------------------------------------------
  28. type Expression = String
  29. type ModuleString = String
  30. ----------------------------------------------------------------
  31. infoExpr :: Options -> ModuleString -> Expression -> FilePath -> IO String
  32. infoExpr opt modstr expr file = (++ "\n") <$> info opt file modstr expr
  33. info :: Options -> FilePath -> ModuleString -> FilePath -> IO String
  34. info opt fileName modstr expr =
  35. inModuleContext opt fileName modstr exprToInfo "Cannot show info"
  36. where
  37. exprToInfo = infoThing expr
  38. ----------------------------------------------------------------
  39. class HasType a where
  40. getType :: GhcMonad m => TypecheckedModule -> a -> m (Maybe (SrcSpan, Type))
  41. instance HasType (LHsExpr Id) where
  42. getType tcm e = do
  43. hs_env <- getSession
  44. (_, mbe) <- Gap.liftIO $ deSugarExpr hs_env modu rn_env ty_env e
  45. return $ (getLoc e, ) <$> CoreUtils.exprType <$> mbe
  46. where
  47. modu = ms_mod $ pm_mod_summary $ tm_parsed_module tcm
  48. rn_env = tcg_rdr_env $ fst $ tm_internals_ tcm
  49. ty_env = tcg_type_env $ fst $ tm_internals_ tcm
  50. instance HasType (LHsBind Id) where
  51. getType _ (L spn FunBind{fun_matches = MatchGroup _ typ}) = return $ Just (spn, typ)
  52. getType _ _ = return Nothing
  53. instance HasType (LPat Id) where
  54. getType _ (L spn pat) = return $ Just (spn, hsPatType pat)
  55. typeExpr :: Options -> ModuleString -> Int -> Int -> FilePath -> IO String
  56. typeExpr opt modstr lineNo colNo file = Info.typeOf opt file modstr lineNo colNo
  57. typeOf :: Options -> FilePath -> ModuleString -> Int -> Int -> IO String
  58. typeOf opt fileName modstr lineNo colNo =
  59. inModuleContext opt fileName modstr exprToType errmsg
  60. where
  61. exprToType = do
  62. modSum <- getModSummary $ mkModuleName modstr
  63. p <- parseModule modSum
  64. tcm@TypecheckedModule{tm_typechecked_source = tcs} <- typecheckModule p
  65. let bs = listifySpans tcs (lineNo, colNo) :: [LHsBind Id]
  66. es = listifySpans tcs (lineNo, colNo) :: [LHsExpr Id]
  67. ps = listifySpans tcs (lineNo, colNo) :: [LPat Id]
  68. bts <- mapM (getType tcm) bs
  69. ets <- mapM (getType tcm) es
  70. pts <- mapM (getType tcm) ps
  71. let sss = map toTup $ sortBy (cmp `on` fst) $ catMaybes $ concat [ets, bts, pts]
  72. return $ convert opt sss
  73. toTup :: (SrcSpan, Type) -> ((Int,Int,Int,Int),String)
  74. toTup (spn, typ) = (fourInts spn, pretty typ)
  75. fourInts :: SrcSpan -> (Int,Int,Int,Int)
  76. fourInts = fromMaybe (0,0,0,0) . Gap.getSrcSpan
  77. cmp a b
  78. | a `isSubspanOf` b = O.LT
  79. | b `isSubspanOf` a = O.GT
  80. | otherwise = O.EQ
  81. errmsg = convert opt ([] :: [((Int,Int,Int,Int),String)])
  82. listifySpans :: Typeable a => TypecheckedSource -> (Int, Int) -> [Located a]
  83. listifySpans tcs lc = listifyStaged TypeChecker p tcs
  84. where
  85. p (L spn _) = isGoodSrcSpan spn && spn `spans` lc
  86. listifyStaged :: Typeable r => Stage -> (r -> Bool) -> GenericQ [r]
  87. listifyStaged s p = everythingStaged s (++) [] ([] `mkQ` (\x -> [x | p x]))
  88. pretty :: Type -> String
  89. pretty = showDocWith OneLineMode . Gap.styleDoc (mkUserStyle neverQualify AllTheWay) . pprTypeForUser False
  90. ----------------------------------------------------------------
  91. -- from ghc/InteractiveUI.hs
  92. infoThing :: String -> Ghc String
  93. infoThing str = do
  94. names <- parseName str
  95. mb_stuffs <- mapM getInfo names
  96. let filtered = filterOutChildren (\(t,_f,_i) -> t) (catMaybes mb_stuffs)
  97. unqual <- getPrintUnqual
  98. return $ Gap.showDocForUser unqual $ vcat (intersperse (text "") $ map (pprInfo False) filtered)
  99. filterOutChildren :: (a -> TyThing) -> [a] -> [a]
  100. filterOutChildren get_thing xs
  101. = [x | x <- xs, not (getName (get_thing x) `elemNameSet` implicits)]
  102. where
  103. implicits = mkNameSet [getName t | x <- xs, t <- implicitTyThings (get_thing x)]
  104. pprInfo :: PrintExplicitForalls -> (TyThing, GHC.Fixity, [Gap.ClsInst]) -> SDoc
  105. pprInfo pefas (thing, fixity, insts)
  106. = pprTyThingInContextLoc pefas thing
  107. $$ show_fixity fixity
  108. $$ vcat (map pprInstance insts)
  109. where
  110. show_fixity fx
  111. | fx == defaultFixity = Outputable.empty
  112. | otherwise = ppr fx <+> ppr (getName thing)
  113. ----------------------------------------------------------------
  114. inModuleContext :: Options -> FilePath -> ModuleString -> Ghc String -> String -> IO String
  115. inModuleContext opt fileName modstr action errmsg =
  116. withGHC (valid ||> invalid ||> return errmsg)
  117. where
  118. valid = do
  119. (file,_) <- initializeGHC opt fileName ["-w"] False
  120. setTargetFile file
  121. _ <- load LoadAllTargets
  122. doif setContextFromTarget action
  123. invalid = do
  124. _ <- initializeGHC opt fileName ["-w"] False
  125. setTargetBuffer
  126. _ <- load LoadAllTargets
  127. doif setContextFromTarget action
  128. setTargetBuffer = do
  129. modgraph <- depanal [mkModuleName modstr] True
  130. let imports = concatMap (map (Gap.showDoc . ppr . unLoc)) $
  131. map ms_imps modgraph ++ map ms_srcimps modgraph
  132. moddef = "module " ++ sanitize modstr ++ " where"
  133. header = moddef : imports
  134. importsBuf <- Gap.toStringBuffer header
  135. clkTime <- Gap.liftIO getCurrentTime
  136. setTargets [Gap.mkTarget (TargetModule $ mkModuleName modstr)
  137. True
  138. (Just (importsBuf, clkTime))]
  139. doif m t = m >>= \ok -> if ok then t else goNext
  140. sanitize = fromMaybe "SomeModule" . listToMaybe . words
  141. setContextFromTarget :: Ghc Bool
  142. setContextFromTarget = depanal [] False >>= Gap.setCtx