Skip to content

Commit 0e60634

Browse files
committed
Generate bytecode/object code on demand
Adds a new rule `GetLinkable` which is called on demand by hscCompileCoreExprHook whenever a linkable is required for a splice. Adds a MonadUnliftIO instance for Action to faciliate the above We write Core Files whenever a linkable could potentially be required for a file (i.e it is in the transitive closure of a module that uses TH/compile time code execution) However, we only generate byte/object code when such a linkable is really required by a splice (i.e. the module is in the transitive closure of any symbol called from a splice). No linkables are stored in `HiFileResult`. If a linkable is required, then it must be obtained via a call to `GetLinkable`. Also use hashes to do fine grained recompilation checking for TH instead of mod times. This simplifies recompilation checking quite a bit.
1 parent 70b9ba3 commit 0e60634

File tree

8 files changed

+374
-298
lines changed

8 files changed

+374
-298
lines changed

ghcide/src/Development/IDE/Core/Compile.hs

Lines changed: 231 additions & 245 deletions
Large diffs are not rendered by default.

ghcide/src/Development/IDE/Core/RuleTypes.hs

Lines changed: 41 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -35,16 +35,16 @@ import GHC.Generics (Generic)
3535

3636
import qualified Data.Binary as B
3737
import Data.ByteString (ByteString)
38-
import qualified Data.ByteString.Lazy as LBS
3938
import Data.Text (Text)
40-
import Data.Time
4139
import Development.IDE.Import.FindImports (ArtifactsLocation)
4240
import Development.IDE.Spans.Common
4341
import Development.IDE.Spans.LocalBindings
4442
import Development.IDE.Types.Diagnostics
4543
import GHC.Serialized (Serialized)
4644
import Language.LSP.Types (Int32,
4745
NormalizedFilePath)
46+
import Development.IDE.GHC.CoreFile
47+
import Control.Exception (assert)
4848

4949
data LinkableType = ObjectLinkable | BCOLinkable
5050
deriving (Eq,Ord,Show, Generic)
@@ -91,6 +91,26 @@ data GenerateCore = GenerateCore
9191
instance Hashable GenerateCore
9292
instance NFData GenerateCore
9393

94+
type instance RuleResult GetLinkable = LinkableResult
95+
96+
data LinkableResult
97+
= LinkableResult
98+
{ linkableHomeMod :: !HomeModInfo
99+
, linkableHash :: !ByteString
100+
-- ^ The hash of the core file
101+
}
102+
103+
instance Show LinkableResult where
104+
show = show . mi_module . hm_iface . linkableHomeMod
105+
106+
instance NFData LinkableResult where
107+
rnf = rwhnf
108+
109+
data GetLinkable = GetLinkable
110+
deriving (Eq, Show, Typeable, Generic)
111+
instance Hashable GetLinkable
112+
instance NFData GetLinkable
113+
94114
data GetImportMap = GetImportMap
95115
deriving (Eq, Show, Typeable, Generic)
96116
instance Hashable GetImportMap
@@ -138,9 +158,10 @@ data TcModuleResult = TcModuleResult
138158
-- ^ Typechecked splice information
139159
, tmrDeferedError :: !Bool
140160
-- ^ Did we defer any type errors for this module?
141-
, tmrRuntimeModules :: !(ModuleEnv UTCTime)
161+
, tmrRuntimeModules :: !(ModuleEnv ByteString)
142162
-- ^ Which modules did we need at runtime while compiling this file?
143163
-- Used for recompilation checking in the presence of TH
164+
-- Stores the hash of their core file
144165
}
145166
instance Show TcModuleResult where
146167
show = show . pm_mod_summary . tmrParsed
@@ -155,30 +176,29 @@ data HiFileResult = HiFileResult
155176
{ hirModSummary :: !ModSummary
156177
-- Bang patterns here are important to stop the result retaining
157178
-- a reference to a typechecked module
158-
, hirHomeMod :: !HomeModInfo
159-
-- ^ Includes the Linkable iff we need object files
160-
, hirIfaceFp :: ByteString
179+
, hirModIface :: !ModIface
180+
, hirModDetails :: ModDetails
181+
-- ^ Populated lazily
182+
, hirIfaceFp :: !ByteString
161183
-- ^ Fingerprint for the ModIface
162-
, hirLinkableFp :: ByteString
163-
-- ^ Fingerprint for the Linkable
164-
, hirRuntimeModules :: !(ModuleEnv UTCTime)
184+
, hirRuntimeModules :: !(ModuleEnv ByteString)
165185
-- ^ same as tmrRuntimeModules
186+
, hirCoreFp :: !(Maybe (CoreFile, ByteString))
187+
-- ^ If we wrote a core file for this module, then its contents (lazily deserialised)
188+
-- along with its hash
166189
}
167190

168191
hiFileFingerPrint :: HiFileResult -> ByteString
169-
hiFileFingerPrint HiFileResult{..} = hirIfaceFp <> hirLinkableFp
170-
171-
mkHiFileResult :: ModSummary -> HomeModInfo -> ModuleEnv UTCTime -> HiFileResult
172-
mkHiFileResult hirModSummary hirHomeMod hirRuntimeModules = HiFileResult{..}
192+
hiFileFingerPrint HiFileResult{..} = hirIfaceFp <> maybe "" snd hirCoreFp
193+
194+
mkHiFileResult :: ModSummary -> ModIface -> ModDetails -> ModuleEnv ByteString -> Maybe (CoreFile, ByteString) -> HiFileResult
195+
mkHiFileResult hirModSummary hirModIface hirModDetails hirRuntimeModules hirCoreFp =
196+
assert (case hirCoreFp of Just (CoreFile{cf_iface_hash}, _)
197+
-> getModuleHash hirModIface == cf_iface_hash
198+
_ -> True)
199+
HiFileResult{..}
173200
where
174-
hirIfaceFp = fingerprintToBS . getModuleHash . hm_iface $ hirHomeMod -- will always be two bytes
175-
hirLinkableFp = case hm_linkable hirHomeMod of
176-
Nothing -> ""
177-
Just (linkableTime -> l) -> LBS.toStrict $
178-
B.encode (fromEnum $ utctDay l, fromEnum $ utctDayTime l)
179-
180-
hirModIface :: HiFileResult -> ModIface
181-
hirModIface = hm_iface . hirHomeMod
201+
hirIfaceFp = fingerprintToBS . getModuleHash $ hirModIface -- will always be two bytes
182202

183203
instance NFData HiFileResult where
184204
rnf = rwhnf

ghcide/src/Development/IDE/Core/Rules.hs

Lines changed: 64 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -99,7 +99,7 @@ import Data.Tuple.Extra
9999
import Development.IDE.Core.Compile
100100
import Development.IDE.Core.FileExists hiding (LogShake, Log)
101101
import Development.IDE.Core.FileStore (getFileContents,
102-
resetInterfaceStore)
102+
getModTime)
103103
import Development.IDE.Core.IdeConfiguration
104104
import Development.IDE.Core.OfInterest hiding (LogShake, Log)
105105
import Development.IDE.Core.PositionMapping
@@ -135,7 +135,7 @@ import Ide.Plugin.Config
135135
import qualified Language.LSP.Server as LSP
136136
import Language.LSP.Types (SMethod (SCustomMethod, SWindowShowMessage), ShowMessageParams (ShowMessageParams), MessageType (MtInfo))
137137
import Language.LSP.VFS
138-
import System.Directory (makeAbsolute)
138+
import System.Directory (makeAbsolute, doesFileExist)
139139
import Data.Default (def, Default)
140140
import Ide.Plugin.Properties (HasProperty,
141141
KeyNameProxy,
@@ -154,6 +154,9 @@ import qualified Development.IDE.Core.Shake as Shake
154154
import qualified Development.IDE.GHC.ExactPrint as ExactPrint hiding (LogShake)
155155
import qualified Development.IDE.Types.Logger as Logger
156156
import qualified Development.IDE.Types.Shake as Shake
157+
import Development.IDE.GHC.CoreFile
158+
import Data.Time.Clock.POSIX (posixSecondsToUTCTime, utcTimeToPOSIXSeconds)
159+
import Control.Monad.IO.Unlift
157160

158161
data Log
159162
= LogShake Shake.Log
@@ -673,9 +676,13 @@ typeCheckRuleDefinition hsc pm = do
673676
setPriority priorityTypeCheck
674677
IdeOptions { optDefer = defer } <- getIdeOptions
675678

676-
linkables_to_keep <- currentLinkables
679+
unlift <- askUnliftIO
680+
let dets = TypecheckHelpers
681+
{ getLinkablesToKeep = unliftIO unlift $ currentLinkables
682+
, getLinkables = unliftIO unlift . uses_ GetLinkable
683+
}
677684
addUsageDependencies $ liftIO $
678-
typecheckModule defer hsc linkables_to_keep pm
685+
typecheckModule defer hsc dets pm
679686
where
680687
addUsageDependencies :: Action (a, Maybe TcModuleResult) -> Action (a, Maybe TcModuleResult)
681688
addUsageDependencies a = do
@@ -752,7 +759,7 @@ ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do
752759
depSessions <- map hscEnv <$> uses_ (GhcSessionDeps_ fullModSummary) deps
753760
ifaces <- uses_ GetModIface deps
754761

755-
let inLoadOrder = map hirHomeMod ifaces
762+
let inLoadOrder = map (\HiFileResult{..} -> HomeModInfo hirModIface hirModDetails Nothing) ifaces
756763
session' <- liftIO $ mergeEnvs hsc mss inLoadOrder depSessions
757764

758765
Just <$> liftIO (newHscEnvEqWithImportPaths (envImportPaths env) session' [])
@@ -768,7 +775,7 @@ getModIfaceFromDiskRule recorder = defineEarlyCutoff (cmapWithPrio LogShake reco
768775
Just session -> do
769776
linkableType <- getLinkableType f
770777
ver <- use_ GetModificationTime f
771-
se@ShakeExtras{ideNc} <- getShakeExtras
778+
ShakeExtras{ideNc} <- getShakeExtras
772779
let m_old = case old of
773780
Shake.Succeeded (Just old_version) v -> Just (v, old_version)
774781
Shake.Stale _ (Just old_version) v -> Just (v, old_version)
@@ -777,9 +784,10 @@ getModIfaceFromDiskRule recorder = defineEarlyCutoff (cmapWithPrio LogShake reco
777784
{ source_version = ver
778785
, old_value = m_old
779786
, get_file_version = use GetModificationTime_{missingFileDiagnostics = False}
787+
, get_linkable_hashes = \fs -> map linkableHash <$> uses_ GetLinkable fs
780788
, regenerate = regenerateHiFile session f ms
781789
}
782-
r <- loadInterface se (hscEnv session) ms linkableType recompInfo
790+
r <- loadInterface (hscEnv session) ms linkableType recompInfo
783791
case r of
784792
(diags, Nothing) -> return (Nothing, (diags, Nothing))
785793
(diags, Just x) -> do
@@ -899,7 +907,7 @@ getModIfaceRule recorder = defineEarlyCutoff (cmapWithPrio LogShake recorder) $
899907
hsc <- hscEnv <$> use_ GhcSessionDeps f
900908
let compile = fmap ([],) $ use GenerateCore f
901909
se <- getShakeExtras
902-
(diags, !hiFile) <- compileToObjCodeIfNeeded se hsc linkableType compile tmr
910+
(diags, !hiFile) <- writeCoreFileIfNeeded se hsc linkableType compile tmr
903911
let fp = hiFileFingerPrint <$> hiFile
904912
hiDiags <- case hiFile of
905913
Just hiFile
@@ -912,10 +920,6 @@ getModIfaceRule recorder = defineEarlyCutoff (cmapWithPrio LogShake recorder) $
912920
let fp = hiFileFingerPrint <$> hiFile
913921
return (fp, ([], hiFile))
914922

915-
-- Record the linkable so we know not to unload it
916-
whenJust (hm_linkable . hirHomeMod =<< mhmi) $ \(LM time mod _) -> do
917-
compiledLinkables <- getCompiledLinkables <$> getIdeGlobalAction
918-
liftIO $ void $ modifyVar' compiledLinkables $ \old -> extendModuleEnv old mod time
919923
pure res
920924

921925
-- | Count of total times we asked GHC to recompile
@@ -960,13 +964,12 @@ regenerateHiFile sess f ms compNeeded = do
960964
Nothing -> pure (diags', Nothing)
961965
Just tmr -> do
962966

963-
-- compile writes .o file
964967
let compile = liftIO $ compileModule (RunSimplifier True) hsc (pm_mod_summary pm) $ tmrTypechecked tmr
965968

966969
se <- getShakeExtras
967970

968971
-- Bang pattern is important to avoid leaking 'tmr'
969-
(diags'', !res) <- compileToObjCodeIfNeeded se hsc compNeeded compile tmr
972+
(diags'', !res) <- writeCoreFileIfNeeded se hsc compNeeded compile tmr
970973

971974
-- Write hi file
972975
hiDiags <- case res of
@@ -994,18 +997,20 @@ regenerateHiFile sess f ms compNeeded = do
994997

995998

996999
-- | HscEnv should have deps included already
997-
compileToObjCodeIfNeeded :: ShakeExtras -> HscEnv -> Maybe LinkableType -> Action (IdeResult ModGuts) -> TcModuleResult -> Action (IdeResult HiFileResult)
998-
compileToObjCodeIfNeeded _ hsc Nothing _ tmr = do
1000+
-- This writes the core file if a linkable is required
1001+
-- The actual linkable will be generated on demand when required by `GetLinkable`
1002+
writeCoreFileIfNeeded :: ShakeExtras -> HscEnv -> Maybe LinkableType -> Action (IdeResult ModGuts) -> TcModuleResult -> Action (IdeResult HiFileResult)
1003+
writeCoreFileIfNeeded _ hsc Nothing _ tmr = do
9991004
incrementRebuildCount
10001005
res <- liftIO $ mkHiFileResultNoCompile hsc tmr
10011006
pure ([], Just $! res)
1002-
compileToObjCodeIfNeeded se hsc (Just linkableType) getGuts tmr = do
1007+
writeCoreFileIfNeeded se hsc (Just _) getGuts tmr = do
10031008
incrementRebuildCount
10041009
(diags, mguts) <- getGuts
10051010
case mguts of
10061011
Nothing -> pure (diags, Nothing)
10071012
Just guts -> do
1008-
(diags', !res) <- liftIO $ mkHiFileResultCompile se hsc tmr guts linkableType
1013+
(diags', !res) <- liftIO $ mkHiFileResultCompile se hsc tmr guts
10091014
pure (diags++diags', res)
10101015

10111016
getClientSettingsRule :: Recorder (WithPriority Log) -> Rules ()
@@ -1037,6 +1042,46 @@ usePropertyAction kn plId p = do
10371042

10381043
-- ---------------------------------------------------------------------
10391044

1045+
getLinkableRule :: Recorder (WithPriority Log) -> Rules ()
1046+
getLinkableRule recorder =
1047+
defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \GetLinkable f -> do
1048+
ModSummaryResult{msrModSummary = ms} <- use_ GetModSummary f
1049+
HiFileResult{hirModIface, hirModDetails, hirCoreFp} <- use_ GetModIface f
1050+
let obj_file = ml_obj_file (ms_location ms)
1051+
core_file = ml_core_file (ms_location ms)
1052+
core_t <- liftIO $ getModTime core_file
1053+
case hirCoreFp of
1054+
Nothing -> error "called GetLinkable for a file without a linkable"
1055+
Just (bin_core, hash) -> do
1056+
session <- use_ GhcSessionDeps f
1057+
ShakeExtras{ideNc} <- getShakeExtras
1058+
let namecache_updater = mkUpdater ideNc
1059+
linkableType <- getLinkableType f >>= \case
1060+
Nothing -> error "called GetLinkable for a file which doesn't need compilation"
1061+
Just t -> pure t
1062+
(warns, hmi) <- case linkableType of
1063+
-- Bytecode needs to be regenerated from the core file
1064+
BCOLinkable -> liftIO $ coreFileToLinkable linkableType (hscEnv session) ms hirModIface hirModDetails bin_core (posixSecondsToUTCTime core_t)
1065+
-- Object code can be read from the disk
1066+
ObjectLinkable -> do
1067+
-- object file is up to date if it is newer than the core file
1068+
-- Can't use a rule like 'GetModificationTime' or 'GetFileExists' because 'coreFileToLinkable' will write the object file, and
1069+
-- thus bump its modification time, forcing this rule to be rerun every time.
1070+
exists <- liftIO $ doesFileExist obj_file
1071+
mobj_time <- liftIO $
1072+
if exists
1073+
then Just <$> getModTime obj_file
1074+
else pure Nothing
1075+
case mobj_time of
1076+
Just obj_t
1077+
| obj_t >= core_t -> pure ([], Just $ HomeModInfo hirModIface hirModDetails (Just $ LM (posixSecondsToUTCTime obj_t) (ms_mod ms) [DotO obj_file]))
1078+
_ -> liftIO $ coreFileToLinkable linkableType (hscEnv session) ms hirModIface hirModDetails bin_core (error "object doesn't have time")
1079+
-- Record the linkable so we know not to unload it
1080+
whenJust (hm_linkable =<< hmi) $ \(LM time mod _) -> do
1081+
compiledLinkables <- getCompiledLinkables <$> getIdeGlobalAction
1082+
liftIO $ void $ modifyVar' compiledLinkables $ \old -> extendModuleEnv old mod time
1083+
return (hash <$ hmi, (warns, LinkableResult <$> hmi <*> pure hash))
1084+
10401085
-- | For now we always use bytecode unless something uses unboxed sums and tuples along with TH
10411086
getLinkableType :: NormalizedFilePath -> Action (Maybe LinkableType)
10421087
getLinkableType f = use_ NeedsCompilation f
@@ -1069,7 +1114,6 @@ needsCompilationRule file = do
10691114
(,) (map (fmap (msrModSummary . fst)) <$> usesWithStale GetModSummaryWithoutTimestamps revdeps)
10701115
(uses NeedsCompilation revdeps)
10711116
pure $ computeLinkableType ms modsums (map join needsComps)
1072-
10731117
pure (Just $ encodeLinkableType res, Just res)
10741118
where
10751119
computeLinkableType :: ModSummary -> [Maybe ModSummary] -> [Maybe LinkableType] -> Maybe LinkableType
@@ -1170,3 +1214,4 @@ mainRule recorder RulesConfig{..} = do
11701214
persistentHieFileRule recorder
11711215
persistentDocMapRule
11721216
persistentImportMapRule
1217+
getLinkableRule recorder

0 commit comments

Comments
 (0)