Skip to content
GitLab
Projects
Groups
Snippets
Help
Loading...
Help
What's new
10
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Open sidebar
Shayne Fletcher
Glasgow Haskell Compiler
Commits
163de258
Commit
163de258
authored
Jul 03, 2013
by
nfrisby
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
include FastString.string_table in CoreMonad.reinitializeGlobals
parent
a5b7ee5f
Changes
2
Show whitespace changes
Inline
Side-by-side
Showing
2 changed files
with
45 additions
and
6 deletions
+45
-6
compiler/simplCore/CoreMonad.lhs
compiler/simplCore/CoreMonad.lhs
+31
-5
compiler/utils/FastString.lhs
compiler/utils/FastString.lhs
+14
-1
No files found.
compiler/simplCore/CoreMonad.lhs
View file @
163de258
...
...
@@ -722,11 +722,12 @@ data CoreReader = CoreReader {
cr_hsc_env :: HscEnv,
cr_rule_base :: RuleBase,
cr_module :: Module,
cr_globals :: ((Bool, [String]),
cr_globals :: (,,) (Bool, [String]) -- from StaticFlags
FastStringTable -- from FastString
#ifdef GHCI
(MVar PersistentLinkerState, Bool)
)
(MVar PersistentLinkerState, Bool)
-- from Linker
#else
()
)
()
#endif
}
...
...
@@ -789,7 +790,7 @@ runCoreM :: HscEnv
-> CoreM a
-> IO (a, SimplCount)
runCoreM hsc_env rule_base us mod m = do
glbls <- liftM
2
(,) saveStaticFlagGlobals saveLinkerGlobals
glbls <- liftM
3
(,
,
) saveStaticFlagGlobals
saveFSTable
saveLinkerGlobals
liftM extract $ runIOEnv (reader glbls) $ unCoreM m state
where
reader glbls = CoreReader {
...
...
@@ -891,6 +892,8 @@ getOrigNameCache = do
%* *
%************************************************************************
Note [Initializing globals]
This is a rather annoying function. When a plugin is loaded, it currently
gets linked against a *newly loaded* copy of the GHC package. This would
not be a problem, except that the new copy has its own mutable state
...
...
@@ -921,13 +924,36 @@ I've threaded the cr_globals through CoreM rather than giving them as an
argument to the plugin function so that we can turn this function into
(return ()) without breaking any plugins when we eventually get 1. working.
-----
We include the FastString table in this mechanism, because we'd like
FastStrings created by the plugin to have the same uniques as similar strings
created by the host compiler itself. For example, this allows plugins to
lookup known names (eg `mkTcOcc "MySpecialType"`) in the GlobalRdrEnv or even
re-invoke the parser.
In particular, the following little sanity test was failing in a plugin
prototyping safe newtype-coercions.
let rdrName = mkModuleName "GHC.NT.Type" `mkRdrQual` mkTcOcc "NT"
putMsgS $ showSDoc dflags $ ppr $ lookupGRE_RdrName rdrName $ mg_rdr_env guts
`mkTcOcc` involves the lookup (or creation) of a FastString. Since the
plugin's FastString.string_table is empty, constructing the RdrName also
allocates new uniques for the FastStrings "GHC.NT.Type" and "NT". These
uniques are almost certainly unequal to the ones that the host compiler
originally assigned to those FastStrings. Thus the lookup fails since the
domain of the GlobalRdrEnv is affected by the RdrName's OccName's FastString's
unique.
\begin{code}
reinitializeGlobals :: CoreM ()
reinitializeGlobals = do
(sf_globals, linker_globals) <- read cr_globals
(sf_globals,
fs_table,
linker_globals) <- read cr_globals
hsc_env <- getHscEnv
let dflags = hsc_dflags hsc_env
liftIO $ restoreStaticFlagGlobals sf_globals
liftIO $ restoreFSTable fs_table
liftIO $ restoreLinkerGlobals linker_globals
liftIO $ setUnsafeGlobalDynFlags dflags
\end{code}
...
...
compiler/utils/FastString.lhs
View file @
163de258
...
...
@@ -91,7 +91,10 @@ module FastString
unpackLitString,
-- ** Operations
lengthLS
lengthLS,
-- * Saving/restoring globals
saveFSTable, restoreFSTable, FastStringTable
) where
#include "HsVersions.h"
...
...
@@ -573,4 +576,14 @@ fsLit x = mkFastString x
forall x . sLit (unpackCString# x) = mkLitString# x #-}
{-# RULES "fslit"
forall x . fsLit (unpackCString# x) = mkFastString# x #-}
--------------------
-- for plugins; see Note [Initializing globals] in CoreMonad
saveFSTable :: IO FastStringTable
saveFSTable = readIORef string_table
restoreFSTable :: FastStringTable -> IO ()
restoreFSTable = writeIORef string_table
\end{code}
Write
Preview
Markdown
is supported
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment