5
5
{-# LANGUAGE CPP #-}
6
6
#include "ghc-api-version.h"
7
7
8
- -- | GHC utility functions. Importantly, code using our GHC should never:
9
- --
10
- -- * Call runGhc, use runGhcFast instead. It's faster and doesn't require config we don't have.
11
- --
12
- -- * Call setSessionDynFlags, use modifyDynFlags instead. It's faster and avoids loading packages.
8
+ -- | General utility functions, mostly focused around GHC operations.
13
9
module Development.IDE.GHC.Util (
14
- lookupPackageConfig ,
10
+ -- * HcsEnv and environment
11
+ HscEnvEq , hscEnv , newHscEnvEq ,
15
12
modifyDynFlags ,
16
13
fakeDynFlags ,
17
- prettyPrint ,
18
14
runGhcEnv ,
19
- textToStringBuffer ,
15
+ -- * GHC wrappers
16
+ prettyPrint ,
17
+ lookupPackageConfig ,
20
18
moduleImportPath ,
21
- HscEnvEq , hscEnv , newHscEnvEq ,
19
+ cgGutsToCoreModule ,
20
+ -- * General utilities
21
+ textToStringBuffer ,
22
22
readFileUtf8 ,
23
23
hDuplicateTo' ,
24
- cgGutsToCoreModule
25
24
) where
26
25
27
26
import Config
@@ -60,6 +59,8 @@ import Development.IDE.Types.Location
60
59
----------------------------------------------------------------------
61
60
-- GHC setup
62
61
62
+ -- | Used to modify dyn flags in preference to calling 'setSessionDynFlags',
63
+ -- since that function also reloads packages (which is very slow).
63
64
modifyDynFlags :: GhcMonad m => (DynFlags -> DynFlags ) -> m ()
64
65
modifyDynFlags f = do
65
66
newFlags <- f <$> getSessionDynFlags
@@ -68,6 +69,7 @@ modifyDynFlags f = do
68
69
modifySession $ \ h ->
69
70
h { hsc_dflags = newFlags, hsc_IC = (hsc_IC h) {ic_dflags = newFlags} }
70
71
72
+ -- | Given a 'UnitId' try and find the associated 'PackageConfig' in the environment.
71
73
lookupPackageConfig :: UnitId -> HscEnv -> Maybe PackageConfig
72
74
lookupPackageConfig unitId env =
73
75
lookupPackage' False pkgConfigMap unitId
@@ -78,14 +80,18 @@ lookupPackageConfig unitId env =
78
80
getPackageConfigMap $ hsc_dflags env
79
81
80
82
81
- -- would be nice to do this more efficiently...
83
+ -- | Convert from the @text@ package to the @GHC@ 'StringBuffer'.
84
+ -- Currently implemented somewhat inefficiently (if it ever comes up in a profile).
82
85
textToStringBuffer :: T. Text -> StringBuffer
83
86
textToStringBuffer = stringToStringBuffer . T. unpack
84
87
85
88
89
+ -- | Pretty print a GHC value using 'fakeDynFlags'.
86
90
prettyPrint :: Outputable a => a -> String
87
91
prettyPrint = showSDoc fakeDynFlags . ppr
88
92
93
+ -- | Run a 'Ghc' monad value using an existing 'HscEnv'. Sets up and tears down all the required
94
+ -- pieces, but designed to be more efficient than a standard 'runGhc'.
89
95
runGhcEnv :: HscEnv -> Ghc a -> IO a
90
96
runGhcEnv env act = do
91
97
filesToClean <- newIORef emptyFilesToClean
@@ -96,8 +102,8 @@ runGhcEnv env act = do
96
102
cleanTempFiles dflags
97
103
cleanTempDirs dflags
98
104
99
- -- Fake DynFlags which are mostly undefined, but define enough to do a
100
- -- little bit .
105
+ -- | A ' DynFlags' value where most things are undefined. It's sufficient to call pretty printing,
106
+ -- but not much else .
101
107
fakeDynFlags :: DynFlags
102
108
fakeDynFlags = defaultDynFlags settings mempty
103
109
where
@@ -120,6 +126,9 @@ fakeDynFlags = defaultDynFlags settings mempty
120
126
, pc_WORD_SIZE= 8
121
127
}
122
128
129
+ -- | Given a module location, and its parse tree, figure out what is the include directory implied by it.
130
+ -- For example, given the file @\/usr\/\Test\/Foo\/Bar.hs@ with the module name @Foo.Bar@ the directory
131
+ -- @\/usr\/Test@ should be on the include path to find sibling modules.
123
132
moduleImportPath :: NormalizedFilePath -> GHC. ParsedModule -> Maybe FilePath
124
133
-- The call to takeDirectory is required since DAML does not require that
125
134
-- the file name matches the module name in the last component.
@@ -137,12 +146,15 @@ moduleImportPath (takeDirectory . fromNormalizedFilePath -> pathDir) pm
137
146
fromNormalizedFilePath $ toNormalizedFilePath $
138
147
moduleNameSlashes $ GHC. moduleName mod'
139
148
140
- -- | An HscEnv with equality.
149
+ -- | An 'HscEnv' with equality. Two values are considered equal
150
+ -- if they are created with the same call to 'newHscEnvEq'.
141
151
data HscEnvEq = HscEnvEq Unique HscEnv
142
152
153
+ -- | Unwrap an 'HsEnvEq'.
143
154
hscEnv :: HscEnvEq -> HscEnv
144
155
hscEnv (HscEnvEq _ x) = x
145
156
157
+ -- | Wrap an 'HscEnv' into an 'HscEnvEq'.
146
158
newHscEnvEq :: HscEnv -> IO HscEnvEq
147
159
newHscEnvEq e = do u <- newUnique; return $ HscEnvEq u e
148
160
@@ -155,18 +167,20 @@ instance Eq HscEnvEq where
155
167
instance NFData HscEnvEq where
156
168
rnf (HscEnvEq a b) = rnf (hashUnique a) `seq` b `seq` ()
157
169
170
+ -- | Read a UTF8 file, with lenient decoding, so it will never raise a decoding error.
158
171
readFileUtf8 :: FilePath -> IO T. Text
159
172
readFileUtf8 f = T. decodeUtf8With T. lenientDecode <$> BS. readFile f
160
173
174
+ -- | Convert from a 'CgGuts' to a 'CoreModule'.
161
175
cgGutsToCoreModule :: SafeHaskellMode -> CgGuts -> ModDetails -> CoreModule
162
176
cgGutsToCoreModule safeMode guts modDetails = CoreModule
163
177
(cg_module guts)
164
178
(md_types modDetails)
165
179
(cg_binds guts)
166
180
safeMode
167
181
168
- -- This is a slightly modified version of hDuplicateTo in GHC.
169
- -- See the inline comment for more details .
182
+ -- | A slightly modified version of ' hDuplicateTo' from GHC.
183
+ -- Importantly, it avoids the bug listed in https://gitlab.haskell.org/ghc/ghc/merge_requests/2318 .
170
184
hDuplicateTo' :: Handle -> Handle -> IO ()
171
185
hDuplicateTo' h1@ (FileHandle path m1) h2@ (FileHandle _ m2) = do
172
186
withHandle__' " hDuplicateTo" h2 m2 $ \ h2_ -> do
0 commit comments