Skip to content

Commit 2d6dbb9

Browse files
committed
update
1 parent 9cb3a1e commit 2d6dbb9

File tree

34 files changed

+770
-35
lines changed

34 files changed

+770
-35
lines changed

ghcide/ghcide.cabal

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -372,7 +372,6 @@ test-suite ghcide-tests
372372
ClientSettingsTests
373373
CodeLensTests
374374
CPPTests
375-
CradleTests
376375
DependentFileTest
377376
DiagnosticTests
378377
ExceptionTests

ghcide/session-loader/Development/IDE/Session.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -647,15 +647,17 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
647647
-- Display a user friendly progress message here: They probably don't know what a cradle is
648648
let progMsg = "Setting up " <> T.pack (takeBaseName (cradleRootDir cradle))
649649
<> " (for " <> T.pack lfp <> ")"
650+
mRunLspT lspEnv $ sendNotification (SMethod_CustomMethod (Proxy @"ghcide/cradle/eopts/before")) (toJSON cfp)
650651
eopts <- mRunLspTCallback lspEnv (\act -> withIndefiniteProgress progMsg Nothing NotCancellable (const act)) $
651652
withTrace "Load cradle" $ \addTag -> do
652653
addTag "file" lfp
653654
old_files <- readIORef cradle_files
654655
res <- cradleToOptsAndLibDir recorder cradle cfp old_files
655656
addTag "result" (show res)
656657
return res
657-
658+
mRunLspT lspEnv $ sendNotification (SMethod_CustomMethod (Proxy @"ghcide/cradle/eopts/after")) (toJSON cfp)
658659
logWith recorder Debug $ LogSessionLoadingResult eopts
660+
mRunLspT lspEnv $ sendNotification (SMethod_CustomMethod (Proxy @"ghcide/cradle/eopts/afterLog")) (toJSON (show $ pretty (LogSessionLoadingResult eopts)))
659661
case eopts of
660662
-- The cradle gave us some options so get to work turning them
661663
-- into and HscEnv.

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

Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -162,6 +162,7 @@ import Language.LSP.Protocol.Types (MessageType (Mess
162162
ShowMessageParams (ShowMessageParams))
163163
import Language.LSP.Server (LspT)
164164
import qualified Language.LSP.Server as LSP
165+
import qualified Language.LSP.Protocol.Message as LSP
165166
import Language.LSP.VFS
166167
import Prelude hiding (mod)
167168
import System.Directory (doesFileExist,
@@ -170,6 +171,7 @@ import System.Info.Extra (isWindows)
170171

171172

172173
import GHC.Fingerprint
174+
import qualified Development.IDE.Session as Session
173175

174176
-- See Note [Guidelines For Using CPP In GHCIDE Import Statements]
175177

@@ -179,12 +181,14 @@ import GHC (mgModSummaries)
179181

180182
#if MIN_VERSION_ghc(9,3,0)
181183
import qualified Data.IntMap as IM
184+
import Data.Row (KnownSymbol)
182185
#endif
183186

184187

185188

186189
data Log
187190
= LogShake Shake.Log
191+
| LogSession Session.Log
188192
| LogReindexingHieFile !NormalizedFilePath
189193
| LogLoadingHieFile !NormalizedFilePath
190194
| LogLoadingHieFileFail !FilePath !SomeException
@@ -214,6 +218,7 @@ instance Pretty Log where
214218
<+> "the HLS version being used, the plugins enabled, and if possible the codebase and file which"
215219
<+> "triggered this warning."
216220
]
221+
LogSession msg -> pretty msg
217222

218223
templateHaskellInstructions :: T.Text
219224
templateHaskellInstructions = "https://haskell-language-server.readthedocs.io/en/latest/troubleshooting.html#static-binaries"
@@ -707,8 +712,24 @@ loadGhcSession recorder ghcSessionDepsConfig = do
707712
return (fingerprint, res)
708713

709714
defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \GhcSession file -> do
715+
-- todo add signal
716+
ShakeExtras{exportsMap, ideTesting = IdeTesting testing, lspEnv, progress} <- getShakeExtras
717+
let
718+
signal' :: KnownSymbol s => Proxy s -> String -> Action ()
719+
signal' msg str = when testing $ liftIO $
720+
mRunLspT lspEnv $
721+
LSP.sendNotification (LSP.SMethod_CustomMethod msg) $
722+
toJSON $ [str]
723+
signal :: KnownSymbol s => Proxy s -> Action ()
724+
signal msg = signal' msg (show file)
725+
726+
727+
728+
signal (Proxy @"GhcSession/start")
710729
IdeGhcSession{loadSessionFun} <- useNoFile_ GhcSessionIO
730+
signal (Proxy @"GhcSession/loadSessionFun/before")
711731
(val,deps) <- liftIO $ loadSessionFun $ fromNormalizedFilePath file
732+
signal (Proxy @"GhcSession/loadSessionFun/after")
712733

713734
-- add the deps to the Shake graph
714735
let addDependency fp = do
@@ -721,6 +742,7 @@ loadGhcSession recorder ghcSessionDepsConfig = do
721742
mapM_ addDependency deps
722743

723744
let cutoffHash = LBS.toStrict $ B.encode (hash (snd val))
745+
signal (Proxy @"GhcSession/done")
724746
return (Just cutoffHash, val)
725747

726748
defineNoDiagnostics (cmapWithPrio LogShake recorder) $ \(GhcSessionDeps_ fullModSummary) file -> do

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

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -137,6 +137,7 @@ import Development.IDE.Graph.Database (ShakeDatabase,
137137
shakeNewDatabase,
138138
shakeProfileDatabase,
139139
shakeRunDatabaseForKeys)
140+
import Development.IDE.Graph.Internal.Profile (collectProfileMemory)
140141
import Development.IDE.Graph.Rule
141142
import Development.IDE.Types.Action
142143
import Development.IDE.Types.Diagnostics
@@ -716,6 +717,7 @@ shakeShut IdeState{..} = do
716717
-- request so we first abort that.
717718
for_ runner cancelShakeSession
718719
void $ shakeDatabaseProfile shakeDb
720+
void $ collectProfileMemory shakeDb
719721
progressStop $ progress shakeExtras
720722
stopMonitoring
721723

ghcide/test/exe/CradleTests.hs

Lines changed: 9 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -205,19 +205,21 @@ sessionDepsArePickedUp :: TestTree
205205
sessionDepsArePickedUp = testSession'
206206
"session-deps-are-picked-up"
207207
$ \dir -> do
208-
liftIO $
209-
writeFileUTF8
210-
(dir </> "hie.yaml")
211-
"cradle: {direct: {arguments: []}}"
212208
-- Open without OverloadedStrings and expect an error.
213209
doc <- createDoc "Foo.hs" "haskell" fooContent
214-
expectDiagnostics [("Foo.hs", [(DiagnosticSeverity_Error, (3, 6), "Couldn't match type")])]
215-
216210
-- Update hie.yaml to enable OverloadedStrings.
217211
liftIO $
218212
writeFileUTF8
219213
(dir </> "hie.yaml")
220214
"cradle: {direct: {arguments: [-XOverloadedStrings]}}"
215+
-- Now no errors.
216+
-- expectDiagnostics [("Foo.hs", [])]
217+
expectNoMoreDiagnostics 3
218+
219+
liftIO $
220+
writeFileUTF8
221+
(dir </> "hie.yaml")
222+
"cradle: {direct: {arguments: []}}"
221223
sendNotification SMethod_WorkspaceDidChangeWatchedFiles $ DidChangeWatchedFilesParams
222224
[FileEvent (filePathToUri $ dir </> "hie.yaml") FileChangeType_Changed ]
223225
-- Send change event.
@@ -226,8 +228,7 @@ sessionDepsArePickedUp = testSession'
226228
.+ #rangeLength .== Nothing
227229
.+ #text .== "\n"
228230
changeDoc doc [change]
229-
-- Now no errors.
230-
expectDiagnostics [("Foo.hs", [])]
231+
expectDiagnostics [("Foo.hs", [(DiagnosticSeverity_Error, (3, 6), "Couldn't match type")])]
231232
where
232233
fooContent =
233234
T.unlines

haskell-language-server.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1666,6 +1666,7 @@ test-suite hls-core-plugin-tests
16661666
CompletionTests
16671667
HighlightTests
16681668
ReferenceTests
1669+
CradleTests
16691670

16701671

16711672
build-depends:

hls-graph/hls-graph.cabal

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -62,6 +62,7 @@ library
6262
Development.IDE.Graph.Internal.Profile
6363
Development.IDE.Graph.Internal.Rules
6464
Development.IDE.Graph.Internal.Types
65+
Development.IDE.Graph.Internal.DataSize
6566
Development.IDE.Graph.KeyMap
6667
Development.IDE.Graph.KeySet
6768
Development.IDE.Graph.Rule
@@ -92,6 +93,7 @@ library
9293
, transformers
9394
, unliftio
9495
, unordered-containers
96+
, ghc-heap
9597

9698
if flag(embed-files)
9799
cpp-options: -DFILE_EMBED
Lines changed: 94 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,94 @@
1+
{-# LANGUAGE BangPatterns #-}
2+
{-# LANGUAGE MagicHash #-}
3+
{-# LANGUAGE UnboxedTuples #-}
4+
5+
{- |
6+
Module : GHC.DataSize
7+
Copyright : (c) Dennis Felsing
8+
License : 3-Clause BSD-style
9+
Maintainer : [email protected]
10+
-}
11+
module Development.IDE.Graph.Internal.DataSize (
12+
closureSize,
13+
recursiveSize,
14+
recursiveSizeNF
15+
)
16+
where
17+
18+
import Control.DeepSeq (NFData, ($!!))
19+
20+
import GHC.Exts
21+
import GHC.Exts.Heap hiding (size)
22+
import GHC.Exts.Heap.Constants (wORD_SIZE)
23+
24+
import Control.Monad
25+
26+
import System.Mem
27+
28+
-- Inspired by Simon Marlow:
29+
-- https://ghcmutterings.wordpress.com/2009/02/12/53/
30+
31+
-- | Calculate size of GHC objects in Bytes. Note that an object may not be
32+
-- evaluated yet and only the size of the initial closure is returned.
33+
closureSize :: a -> IO Word
34+
closureSize x = do
35+
rawWds <- getClosureRawWords x
36+
return . fromIntegral $ length rawWds * wORD_SIZE
37+
38+
-- | Calculate the recursive size of GHC objects in Bytes. Note that the actual
39+
-- size in memory is calculated, so shared values are only counted once.
40+
--
41+
-- Call with
42+
-- @
43+
-- recursiveSize $! 2
44+
-- @
45+
-- to force evaluation to WHNF before calculating the size.
46+
--
47+
-- Call with
48+
-- @
49+
-- recursiveSize $!! \"foobar\"
50+
-- @
51+
-- ($!! from Control.DeepSeq) to force full evaluation before calculating the
52+
-- size.
53+
--
54+
-- A garbage collection is performed before the size is calculated, because
55+
-- the garbage collector would make heap walks difficult.
56+
--
57+
-- This function works very quickly on small data structures, but can be slow
58+
-- on large and complex ones. If speed is an issue it's probably possible to
59+
-- get the exact size of a small portion of the data structure and then
60+
-- estimate the total size from that.
61+
62+
recursiveSize :: a -> IO Word
63+
recursiveSize x = do
64+
performGC
65+
liftM snd $ go ([], 0) $ asBox x
66+
where go (!vs, !acc) b@(Box y) = do
67+
isElem <- liftM or $ mapM (areBoxesEqual b) vs
68+
if isElem
69+
then return (vs, acc)
70+
else do
71+
size <- closureSize y
72+
closure <- getClosureData y
73+
foldM go (b : vs, acc + size) $ allClosures closure
74+
75+
-- | Calculate the recursive size of GHC objects in Bytes after calling
76+
-- Control.DeepSeq.force on the data structure to force it into Normal Form.
77+
-- Using this function requires that the data structure has an `NFData`
78+
-- typeclass instance.
79+
80+
recursiveSizeNF :: NFData a => a -> IO Word
81+
recursiveSizeNF x = recursiveSize $!! x
82+
83+
-- | Adapted from 'GHC.Exts.Heap.getClosureRaw' which isn't exported.
84+
--
85+
-- This returns the raw words of the closure on the heap. Once back in the
86+
-- Haskell world, the raw words that hold pointers may be outdated after a
87+
-- garbage collector run.
88+
getClosureRawWords :: a -> IO [Word]
89+
getClosureRawWords x = do
90+
case unpackClosure# x of
91+
(# _iptr, dat, _pointers #) -> do
92+
let nelems = (I# (sizeofByteArray# dat)) `div` wORD_SIZE
93+
end = fromIntegral nelems - 1
94+
pure [W# (indexWordArray# dat i) | I# i <- [0.. end] ]

hls-graph/src/Development/IDE/Graph/Internal/Profile.hs

Lines changed: 15 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,8 +5,9 @@
55

66
{- HLINT ignore "Redundant bracket" -} -- a result of CPP expansion
77

8-
module Development.IDE.Graph.Internal.Profile (writeProfile) where
8+
module Development.IDE.Graph.Internal.Profile (writeProfile, collectProfileMemory) where
99

10+
import Control.Concurrent.STM (atomically)
1011
import Control.Concurrent.STM.Stats (readTVarIO)
1112
import Data.Bifunctor
1213
import qualified Data.ByteString.Lazy.Char8 as LBS
@@ -23,13 +24,16 @@ import Data.Maybe
2324
import Data.Time (getCurrentTime)
2425
import Data.Time.Format.ISO8601 (iso8601Show)
2526
import Development.IDE.Graph.Internal.Database (getDirtySet)
27+
import Development.IDE.Graph.Internal.DataSize
2628
import Development.IDE.Graph.Internal.Key
2729
import Development.IDE.Graph.Internal.Paths
2830
import Development.IDE.Graph.Internal.Types
2931
import qualified Language.Javascript.DGTable as DGTable
3032
import qualified Language.Javascript.Flot as Flot
3133
import qualified Language.Javascript.JQuery as JQuery
34+
import ListT (toList)
3235
import Numeric.Extra (showDP)
36+
import qualified StmContainers.Map as SMap
3337
import System.FilePath
3438
import System.IO.Unsafe (unsafePerformIO)
3539
import System.Time.Extra (Seconds)
@@ -39,6 +43,16 @@ import Data.FileEmbed
3943
import Language.Haskell.TH.Syntax (runIO)
4044
#endif
4145

46+
data DataBaseProfileMemory = ProfileMemory
47+
{}
48+
49+
collectProfileMemory :: ShakeDatabase -> IO DataBaseProfileMemory
50+
collectProfileMemory (ShakeDatabase _ _ Database{databaseValues}) = do
51+
kvss <- atomically $ (fmap . fmap) (first renderKey) $ toList $ SMap.listT databaseValues
52+
kvs <- mapM (\(k, v)-> fmap (k, ) (recursiveSize v)) $ kvss
53+
writeFile "profile-memory.txt" $ show kvs
54+
pure ProfileMemory
55+
4256
-- | Generates an report given some build system profiling data.
4357
writeProfile :: FilePath -> Database -> IO ()
4458
writeProfile out db = do

0 commit comments

Comments
 (0)