Home
last modified time | relevance | path

Searched refs:hsc_env (Results 1 – 25 of 69) sorted by relevance

123

/dports/lang/ghc/ghc-8.10.7/compiler/main/
H A DInteractiveEval.hs130 mkHistory hsc_env hval bi = History hval bi (findEnclosingDecls hsc_env bi) function
164 hsc_env <- getSession
165 let ic = hsc_IC hsc_env
187 hsc_env <- getSession
204 hsc_env <- getSession
243 hsc_env <- getSession
275 hsc_env <- getSession
395 hsc_env <- getSession
446 hsc_env <- getSession
649 pushResume hsc_env resume = hsc_env { hsc_IC = ictxt1 } function
[all …]
H A DDynamicLoading.hs64 initializePlugins hsc_env df
81 loadPlugins hsc_env
87 dflags = hsc_dflags hsc_env
100 checkExternalInterpreter hsc_env
102 hsc_env mod_name
106 checkExternalInterpreter hsc_env =
111 dflags = hsc_dflags hsc_env
142 = (initTcInteractive hsc_env $
168 where dflags = hsc_dflags hsc_env
189 dflags = hsc_dflags hsc_env
[all …]
H A DHscMain.hs294 hsc_env <- getHscEnv
309 = runHsc hsc_env $ ioMsgMaybe $ isGHCiMonad hsc_env name
313 hsc_env <- getHscEnv
320 hsc_env <- getHscEnv
327 hscParse hsc_env mod_summary = runHsc hsc_env $ hscParse' mod_summary function
453 hscTypecheckRename hsc_env mod_summary rdr_module = runHsc hsc_env $ do function
1113 hscCheckSafe hsc_env m l = runHsc hsc_env $ do function
1122 hscGetSafe hsc_env m l = runHsc hsc_env $ do function
1638 hscParsedStmt hsc_env stmt = runInteractiveHsc hsc_env $ do function
1682 hscParsedDecls hsc_env decls = runInteractiveHsc hsc_env $ do function
[all …]
H A DFinder.hs74 flushFinderCaches hsc_env =
78 fc_ref = hsc_FC hsc_env
124 findPluginModule hsc_env mod_name =
125 findHomeModule hsc_env mod_name
136 findExactModule hsc_env mod =
183 = findLookupResult hsc_env
190 = findLookupResult hsc_env
281 dflags = hsc_dflags hsc_env
304 dflags = hsc_dflags hsc_env
358 modLocationCache hsc_env mod $
[all …]
H A DGHC.hs483 hsc_env <- getSession
906 hsc_env <- getSession
919 hsc_env <- getSession
951 hsc_env <- getSession
988 hsc_env <- getSession
1116 return (icPrintUnqual (hsc_dflags hsc_env) (hsc_IC hsc_env))
1150 = do eps <- hscEPS hsc_env
1257 getGRE = withSession $ \hsc_env-> return $ ic_rn_gbl_env (hsc_IC hsc_env)
1269 hsc_env <- getSession
1272 Nothing -> loadUnqualIfaces hsc_env (hsc_IC hsc_env)
[all …]
H A DGhcMake.hs125 hsc_env <- getSession
151 hsc_env <- getSession
283 hsc_env <- getSession
345 modifySession $ \hsc_env -> hsc_env { hsc_mod_graph = mod_graph }
347 hsc_env <- getSession
591 modifySession $ \hsc_env -> hsc_env{ hsc_HPT = hpt5 }
614 discardProg hsc_env
622 discardIC hsc_env
1325 = hsc_env { hsc_dflags = (hsc_dflags hsc_env) function
1804 = typecheckLoop (hsc_dflags hsc_env) hsc_env (map ms_mod_name non_boot)
[all …]
/dports/devel/hs-ormolu/ormolu-0.4.0.0/_cabal_deps/ghc-lib-parser-9.2.1.20211101/compiler/GHC/Driver/
H A DEnv.hs69 runHsc hsc_env (Hsc hsc) = do function
71 printOrThrowWarnings (hsc_logger hsc_env) (hsc_dflags hsc_env) w
76 mkInteractiveHscEnv hsc_env =
77 let ic = hsc_IC hsc_env
85 runInteractiveHsc hsc_env = runHsc (mkInteractiveHscEnv hsc_env) function
165 hscEPS hsc_env = readIORef (hsc_EPS hsc_env) function
190 hptAnns hsc_env Nothing = hptAllThings (md_anns . hm_details) hsc_env function
193 hptAllThings extract hsc_env = concatMap extract (eltsHpt (hsc_HPT hsc_env))
231 eps <- hscEPS hsc_env
250 lookupType hsc_env name = do function
[all …]
H A DPlugins.hs246 plugins hsc_env =
247 map lpPlugin (hsc_plugins hsc_env) ++
248 map spPlugin (hsc_static_plugins hsc_env)
252 withPlugins hsc_env transformation input = foldM go input (plugins hsc_env) function
257 mapPlugins hsc_env f = map (\(PluginWithArgs p opts) -> f p opts) (plugins hsc_env) function
261 withPlugins_ hsc_env transformation input
263 (plugins hsc_env)
/dports/lang/ghc/ghc-8.10.7/compiler/ghci/
H A DGHCi.hs267 evalIO hsc_env fhv = do function
273 evalString hsc_env fhv = do function
287 mallocData hsc_env bs = iservCmd hsc_env (MallocData bs) function
357 getClosure hsc_env ref =
363 seqHValue hsc_env ref =
371 initObjLinker hsc_env = iservCmd hsc_env InitLinker function
422 loadDLL hsc_env str = iservCmd hsc_env (LoadDLL str) function
430 loadObj hsc_env path = do function
453 resolveObjs hsc_env = successIf <$> iservCmd hsc_env ResolveObjs function
456 findSystemLibrary hsc_env str = iservCmd hsc_env (FindSystemLibrary str) function
[all …]
H A DLinker.hs159 getHValue hsc_env name = do function
161 initDynLinker hsc_env
261 initDynLinker hsc_env = do function
275 initObjLinker hsc_env
287 initDynLinker hsc_env
525 ; initDynLinker hsc_env
758 initDynLinker hsc_env
804 initDynLinker hsc_env
1066 unload hsc_env linkables
1227 initDynLinker hsc_env
[all …]
H A DDebugger.hs62 modifySession $ \hsc_env ->
63 hsc_env{hsc_IC = substInteractiveContext (hsc_IC hsc_env) subst} function
88 hsc_env <- getSession
101 withSession $ \hsc_env -> do
116 hsc_env <- getSession
118 let ictxt = hsc_IC hsc_env
128 dl = hsc_dynLinker hsc_env
155 n <- newGrimName hsc_env name
171 hsc_env <- getSession
195 setSession hsc_env
[all …]
H A DByteCodeLink.hs66 linkBCO hsc_env ie ce bco_ix breakarray
78 lookupLiteral hsc_env _ (BCONPtrLbl sym) = do function
79 Ptr a# <- lookupStaticPtr hsc_env sym
81 lookupLiteral hsc_env ie (BCONPtrItbl nm) = do function
82 Ptr a# <- lookupIE hsc_env ie nm
90 m <- lookupSymbol hsc_env addr_of_label_string
97 lookupIE hsc_env ie con_nm =
102 m <- lookupSymbol hsc_env sym_to_find1
116 lookupPrimOp hsc_env primop = do function
135 m <- lookupSymbol hsc_env sym_to_find
[all …]
H A DByteCodeItbls.hs34 mkITbls hsc_env tcs =
36 mapM (mkITbl hsc_env) (filter isDataTyCon tcs)
39 mkITbl hsc_env tc
41 = make_constr_itbls hsc_env dcs
52 make_constr_itbls hsc_env cons =
55 dflags = hsc_dflags hsc_env
74 r <- iservCmd hsc_env (MkConInfoTable ptrs' nptrs_really
/dports/devel/hs-ormolu/ormolu-0.4.0.0/_cabal_deps/ghc-lib-parser-9.2.1.20211101/compiler/GHC/Driver/Pipeline/
H A DMonad.hs74 hsc_env :: HscEnv, function
91 pipeStateDynFlags = hsc_dflags . hsc_env
117 getPipeSession = P $ \_env state -> return (state, hsc_env state)
120 getDynFlags = P $ \_env state -> return (state, hsc_dflags (hsc_env state))
123 getLogger = P $ \_env state -> return (state, hsc_logger (hsc_env state))
127 return (state{hsc_env= (hsc_env state){ hsc_dflags = dflags }}, ())
131 let hsc_env' = (hsc_env state){ hsc_plugins = dyn, hsc_static_plugins = static } function
132 in return (state{hsc_env = hsc_env'}, ())
/dports/lang/ghc/ghc-8.10.7/compiler/backpack/
H A DDriverBkp.hs76 modifySession (\hsc_env -> hsc_env {hsc_dflags = dflags})
297 hsc_env <- getSession
396 hsc_env <- getSession
441 setSession hsc_env = do
443 writeMutVar s hsc_env
455 overHscDynFlags f hsc_env = hsc_env { hsc_dflags = f (hsc_dflags hsc_env) }
467 hsc_env <- getSession
473 hsc_env <- getSession
667 hsc_env <- getSession
718 = do hsc_env <- getSession
[all …]
H A DNameShape.hs108 extendNameShape hsc_env ns as =
112 as1 <- mapM (liftIO . substNameAvailInfo hsc_env nsubst) (ns_exports ns)
113 as2 <- mapM (liftIO . substNameAvailInfo hsc_env nsubst) as
182 substNameAvailInfo hsc_env env (AvailTC n ns fs) =
185 <$> mapM (initIfaceLoad hsc_env . setNameModule mb_mod) ns
186 <*> mapM (setNameFieldSelector hsc_env mb_mod) fs
191 setNameFieldSelector hsc_env mb_mod (FieldLabel l b sel) = do function
192 sel' <- initIfaceLoad hsc_env $ setNameModule mb_mod sel
/dports/lang/ghc/ghc-8.10.7/compiler/iface/
H A DMkIface.hs142 mkPartialIface hsc_env mod_details
237 mkIface_ hsc_env
322 dflags = hsc_dflags hsc_env
355 mkHashFun hsc_env eps name
361 dflags = hsc_dflags hsc_env
362 hpt = hsc_HPT hsc_env
414 addFingerprints hsc_env iface0
416 eps <- hscEPS hsc_env
712 dflags = hsc_dflags hsc_env
750 eps <- hscEPS hsc_env
[all …]
H A DIfaceEnv.hs73 newInteractiveBinder hsc_env occ loc
74 = do { let mod = icInteractiveModule (hsc_IC hsc_env)
75 ; updNameCacheIO hsc_env mod occ $ \name_cache ->
131 mkNameCacheUpdater = do { hsc_env <- getTopEnv
132 ; let !ncRef = hsc_NC hsc_env
138 hsc_env <- getTopEnv
139 ; liftIO $ updNameCacheIO hsc_env mod occ upd_fn }
145 updNameCacheIO hsc_env mod occ upd_fn = do { function
155 ; updNameCache (hsc_NC hsc_env) upd_fn }
176 lookupOrigIO hsc_env mod occ
[all …]
/dports/lang/ghc/ghc-8.10.7/compiler/deSugar/
H A DDsUsage.hs109 mkUsageInfo hsc_env this_mod dir_imp_mods used_names dependent_files merged
112 eps <- hscEPS hsc_env
114 plugin_usages <- mapM (mkPluginUsage hsc_env) pluginModules
115 let mod_usages = mk_mod_usage_info (eps_PIT eps) hsc_env this_mod
167 mkPluginUsage hsc_env pluginModule
201 foundM <- findPluginModule hsc_env pNm
212 dflags = hsc_dflags hsc_env
221 foundM <- findImportedModule hsc_env nm Nothing
243 mk_mod_usage_info pit hsc_env this_mod direct_imports used_names
246 hpt = hsc_HPT hsc_env
[all …]
H A DDsMonad.hs175 ; hsc_env <- getTopEnv
182 initDs hsc_env tcg_env thing_inside
185 ; runDs hsc_env envs thing_inside
192 mkDsEnvsFromTcGbl hsc_env msg_var tcg_env
194 ; let dflags = hsc_dflags hsc_env
206 runDs hsc_env (ds_gbl, ds_lcl) thing_inside
216 where dflags = hsc_dflags hsc_env
220 initDsWithModGuts hsc_env guts thing_inside
223 ; let dflags = hsc_dflags hsc_env
238 ; runDs hsc_env envs thing_inside
[all …]
H A DDesugar.hs83 deSugar hsc_env
115 = do { let dflags = hsc_dflags hsc_env
127 then addTicksToBinds hsc_env mod mod_loc
130 ; (msgs, mb_res) <- initDs hsc_env tcg_env $
161 ; endPassIO hsc_env print_unqual CoreDesugar final_pgm rules_for_imps
171 map lpModule (cachedPlugins (hsc_dflags hsc_env))
172 ; deps <- mkDependencies (thisInstalledUnitId (hsc_dflags hsc_env))
178 ; usages <- mkUsageInfo hsc_env mod (imp_mods imports) used_names
261 deSugarExpr hsc_env tc_expr = do { function
262 let dflags = hsc_dflags hsc_env
[all …]
/dports/lang/ghc/ghc-8.10.7/compiler/typecheck/
H A DTcBackpack.hs262 findExtraSigImports' hsc_env HsigFile modname =
264 (initIfaceLoad hsc_env
287 implicitRequirements hsc_env normal_imports
298 implicitRequirements' hsc_env normal_imports
306 where dflags = hsc_dflags hsc_env
333 tcRnCheckUnitId hsc_env uid =
337 initTc hsc_env
344 dflags = hsc_dflags hsc_env
360 dflags = hsc_dflags hsc_env
501 hsc_env <- getTopEnv
[all …]
H A DTcRnDriver.hs172 withTcPlugins hsc_env $ withHoleFitPlugins hsc_env $
181 dflags = hsc_dflags hsc_env
205 tcRnModuleTcRnM hsc_env mod_sum
327 tcRnImports hsc_env import_decls
1852 = initTcInteractive hsc_env $ withTcPlugins hsc_env $ withHoleFitPlugins hsc_env $
1965 tcRnStmt hsc_env rdr_stmt
2337 isGHCiMonad hsc_env ty
2610 tcRnLookupName hsc_env name
2638 tcRnGetInfo hsc_env name
2640 do { loadUnqualIfaces hsc_env (hsc_IC hsc_env)
[all …]
/dports/devel/hs-haskell-language-server/haskell-language-server-1.4.0/_cabal_deps/ghc-exactprint-0.6.4/tests/examples/ghc80/
H A DFrontendPlugin.hs7 import DriverPipeline hiding ( hsc_env )
30 hsc_env <- GHC.getSession
37 then liftIO (oneShot hsc_env StopLn srcs)
40 o_files <- mapM (\x -> liftIO $ compileFile hsc_env StopLn x)
/dports/devel/hs-haskell-language-server/haskell-language-server-1.4.0/_cabal_deps/ghc-lib-parser-8.10.7.20210828/compiler/main/
H A DPipelineMonad.hs64 hsc_env :: HscEnv, function
81 pipeStateDynFlags = hsc_dflags . hsc_env
107 getDynFlags = P $ \_env state -> return (state, hsc_dflags (hsc_env state))
111 return (state{hsc_env= (hsc_env state){ hsc_dflags = dflags }}, ())

123