@@ -987,33 +987,88 @@ mkDetailsFromIface session iface linkable = do
987
987
initIfaceLoad hsc' (typecheckIface iface)
988
988
return (HomeModInfo iface details linkable)
989
989
990
+
990
991
-- | Non-interactive, batch version of 'InteractiveEval.getDocs'.
991
992
-- The interactive paths create problems in ghc-lib builds
992
993
--- and leads to fun errors like "Cannot continue after interface file error".
993
994
getDocsBatch
994
995
:: HscEnv
995
996
-> Module -- ^ a moudle where the names are in scope
996
997
-> [Name ]
997
- -> IO [Either String (Maybe HsDocString , Map. Map Int HsDocString )]
998
+ -- 2021-11-19: NOTE: Don't forget these 'Map' currently lazy.
999
+ -- 2021-11-18: NOTE: Map Int would become IntMap if next GHCs.
1000
+ -> IO (Either ErrorMessages (Map. Map Name (Either GetDocsFailure (Maybe HsDocString , Maybe (Map. Map Int HsDocString )))))
1001
+ -- ^ Return a 'Map' of 'Name's to 'Either' (no docs messages) (general doc body & arg docs)
998
1002
getDocsBatch hsc_env _mod _names = do
999
- ((_warns,errs), res) <- initTc hsc_env HsSrcFile False _mod fakeSpan $ forM _names $ \ name ->
1000
- case nameModule_maybe name of
1001
- Nothing -> return (Left $ NameHasNoModule name)
1002
- Just mod -> do
1003
- ModIface { mi_doc_hdr = mb_doc_hdr
1004
- , mi_decl_docs = DeclDocMap dmap
1005
- , mi_arg_docs = ArgDocMap amap
1006
- } <- loadModuleInterface " getModuleInterface" mod
1007
- if isNothing mb_doc_hdr && Map. null dmap && Map. null amap
1008
- then pure (Left (NoDocsInIface mod $ compiled name))
1009
- else pure (Right ( Map. lookup name dmap
1010
- , Map. findWithDefault Map. empty name amap))
1011
- case res of
1012
- Just x -> return $ map (first $ T. unpack . showGhc) x
1013
- Nothing -> throwErrors errs
1014
- where
1015
- throwErrors = liftIO . throwIO . mkSrcErr
1016
- compiled n =
1003
+ ((_warns,errs), res) <- initTc hsc_env HsSrcFile False _mod fakeSpan $ Map. fromList <$> traverse undefined undefined
1004
+ pure $ maybeToEither errs res
1005
+ where
1006
+ mapOfRequestedDocs :: IOEnv (Env TcGblEnv TcLclEnv ) (Map Name (Maybe HsDocString , Maybe (Map Int HsDocString )))
1007
+ mapOfRequestedDocs = Map. fromList . foldMap getAskedIfaceDocs <$> loadIfaces
1008
+
1009
+ getAskedIfaceDocs :: ((Map Name HsDocString , Map Name (Map Int HsDocString )), [Name ]) -> [(Name , (Maybe HsDocString , Maybe (Map Int HsDocString )))]
1010
+ getAskedIfaceDocs a = lookupDocs <$> snd a
1011
+ where
1012
+ lookupDocs :: Name -> (Name , (Maybe HsDocString , Maybe (Map Int HsDocString )))
1013
+ lookupDocs n = (n, bimap (Map. lookup n) (Map. lookup n) $ fst a)
1014
+
1015
+ loadIfaces :: IOEnv (Env TcGblEnv TcLclEnv ) [((Map Name HsDocString , Map Name (Map Int HsDocString )), [Name ])]
1016
+ loadIfaces = mkOneEnv (fmap (first getIfaceGenNArgDocMaps) loadModules)
1017
+ where
1018
+ mkOneEnv :: Applicative env => [(env ms , ns )] -> env [(ms , ns )]
1019
+ mkOneEnv a = traverse (fmap swap . sequenceA . swap) a
1020
+
1021
+ getIfaceGenNArgDocMaps :: TcRn ModIface -> IOEnv (Env TcGblEnv TcLclEnv ) (Map Name HsDocString , Map Name (Map Int HsDocString ))
1022
+ getIfaceGenNArgDocMaps mi = do
1023
+ ModIface
1024
+ { mi_doc_hdr = mb_doc_hdr
1025
+ , mi_decl_docs = DeclDocMap dmap
1026
+ , mi_arg_docs = ArgDocMap amap
1027
+ }
1028
+ <- mi
1029
+ pure $
1030
+ if isNothing mb_doc_hdr && Map. null dmap && Map. null amap
1031
+ then error " Instead of 'error' here handle 'NoDocsInIface mod $ isCompiled name' case"
1032
+ else (dmap, amap)
1033
+
1034
+ loadModules :: [(TcRn ModIface , [Name ])]
1035
+ loadModules = fmap loadAvailableModules namesGroupedByModule
1036
+ where
1037
+ loadAvailableModules :: (Module , [Name ]) -> (TcRn ModIface , [Name ])
1038
+ loadAvailableModules = first loadModuleInterfaceOnce
1039
+
1040
+
1041
+ loadModuleInterfaceOnce :: Module -> TcRn ModIface
1042
+ loadModuleInterfaceOnce =
1043
+ loadModuleInterface " getModuleInterface"
1044
+
1045
+ namesGroupedByModule :: [(Module , [Name ])]
1046
+ namesGroupedByModule =
1047
+ groupSort $ fmap (first (fromMaybe (error " Instead of 'error' handle here 'NameHasNoModule' case" ) . nameModule_maybe) . dupe) _names
1048
+
1049
+ -- modulesPartitionedOnAvalability :: [(Either (Name -> GetDocsFailure) Module, [Name])]
1050
+ -- modulesPartitionedOnAvalability = fmap partitionOnModuleAvalibility namesGroupedByModule
1051
+
1052
+ -- partitionOnModuleAvalibility :: (Maybe Module, [Name]) -> (Either (Name -> GetDocsFailure) Module, [Name])
1053
+ -- partitionOnModuleAvalibility =
1054
+ -- first (maybeToEither NameHasNoModule)
1055
+
1056
+
1057
+ -- 2021-11-18: NOTE: This code initially was taken from: https://hackage.haskell.org/package/ghc-9.2.1/docs/src/GHC.Runtime.Eval.html#getDocs
1058
+ findNameInfo :: Maybe Module -> Name -> IOEnv (Env TcGblEnv TcLclEnv ) (Name , Either GetDocsFailure (Maybe HsDocString , Maybe (Map. Map Int HsDocString )))
1059
+ findNameInfo Nothing name = return (name, Left $ NameHasNoModule name)
1060
+ findNameInfo (Just mod ) name = do
1061
+ ModIface
1062
+ { mi_doc_hdr = mb_doc_hdr
1063
+ , mi_decl_docs = DeclDocMap dmap
1064
+ , mi_arg_docs = ArgDocMap amap
1065
+ }
1066
+ <- loadModuleInterface " getModuleInterface" mod
1067
+ pure . (name,) $
1068
+ if isNothing mb_doc_hdr && Map. null dmap && Map. null amap
1069
+ then Left $ NoDocsInIface mod $ isCompiled name
1070
+ else Right (Map. lookup name dmap, Map. lookup name amap)
1071
+ isCompiled n =
1017
1072
-- TODO: Find a more direct indicator.
1018
1073
case nameSrcLoc n of
1019
1074
RealSrcLoc {} -> False
0 commit comments