Skip to content

Commit 671211e

Browse files
committed
convert to contravariant logging style part 1, uses additional hardcoded log file to see it side by side with original logging
1 parent a8aa016 commit 671211e

File tree

10 files changed

+378
-116
lines changed

10 files changed

+378
-116
lines changed

exe/Main.hs

Lines changed: 37 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,21 +1,47 @@
11
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
22
-- SPDX-License-Identifier: Apache-2.0
3+
{-# LANGUAGE NamedFieldPuns #-}
34
{-# LANGUAGE OverloadedStrings #-}
4-
{-# LANGUAGE RecordWildCards #-}
55
module Main(main) where
66

7-
import Ide.Arguments (Arguments (..), GhcideArguments (..),
8-
getArguments)
9-
import Ide.Main (defaultMain)
10-
import Plugins
7+
import Data.Function ((&))
8+
import Data.Text (Text)
9+
import qualified Data.Text as Text
10+
import Development.IDE.Types.Logger (Priority (Debug, Info),
11+
WithPriority (WithPriority, priority),
12+
cfilter, cmap,
13+
withDefaultTextWithPriorityRecorder)
14+
import Ide.Arguments (Arguments (..),
15+
GhcideArguments (..),
16+
getArguments)
17+
import Ide.Main (defaultMain)
18+
import qualified Ide.Main as IdeMain
19+
import qualified Plugins
20+
21+
22+
data Log
23+
= LogIdeMain IdeMain.Log
24+
| LogPlugins Plugins.Log
25+
deriving Show
26+
27+
logToTextWithPriority :: Log -> WithPriority Text
28+
logToTextWithPriority = WithPriority Info . Text.pack . show
1129

1230
main :: IO ()
1331
main = do
14-
args <- getArguments "haskell-language-server" (idePlugins False)
32+
args <- getArguments "haskell-language-server" (Plugins.idePlugins undefined False)
33+
34+
let (minPriority, logFilePath, includeExamplePlugins) =
35+
case args of
36+
Ghcide GhcideArguments{ argsTesting, argsDebugOn, argsLogFile, argsExamplePlugin } ->
37+
let minPriority = if argsDebugOn || argsTesting then Debug else Info
38+
in (minPriority, argsLogFile, argsExamplePlugin)
39+
_ -> (Info, Nothing, False)
1540

16-
let withExamples =
17-
case args of
18-
Ghcide GhcideArguments{..} -> argsExamplePlugin
19-
_ -> False
41+
withDefaultTextWithPriorityRecorder (Just "/home/jon/bls.log") $ \textWithPriorityRecorder -> do
42+
let recorder =
43+
textWithPriorityRecorder
44+
& cfilter (\WithPriority{ priority } -> priority >= minPriority)
45+
& cmap logToTextWithPriority
2046

21-
defaultMain args (idePlugins withExamples)
47+
defaultMain (cmap LogIdeMain recorder) args (Plugins.idePlugins (cmap LogPlugins recorder) includeExamplePlugins)

exe/Plugins.hs

Lines changed: 10 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ import Ide.Types (IdePlugins)
77

88
-- fixed plugins
99
import Development.IDE (IdeState)
10-
import Development.IDE.Plugin.HLS.GhcIde as GhcIde
10+
import Development.IDE.Plugin.HLS.GhcIde as GhcIde hiding (Log)
1111
import Ide.Plugin.Example as Example
1212
import Ide.Plugin.Example2 as Example2
1313

@@ -91,18 +91,24 @@ import Ide.Plugin.StylishHaskell as StylishHaskell
9191
#endif
9292

9393
#if brittany
94+
import qualified Development.IDE.Plugin.HLS.GhcIde as Ghcide
95+
import Development.IDE.Types.Logger (Recorder, cmap)
9496
import Ide.Plugin.Brittany as Brittany
9597
#endif
9698

99+
data Log
100+
= LogGhcide Ghcide.Log
101+
deriving Show
102+
97103
-- ---------------------------------------------------------------------
98104

99105
-- | The plugins configured for use in this instance of the language
100106
-- server.
101107
-- These can be freely added or removed to tailor the available
102108
-- features of the server.
103109

104-
idePlugins :: Bool -> IdePlugins IdeState
105-
idePlugins includeExamples = pluginDescToIdePlugins allPlugins
110+
idePlugins :: Recorder Log -> Bool -> IdePlugins IdeState
111+
idePlugins recorder includeExamples = pluginDescToIdePlugins allPlugins
106112
where
107113
allPlugins = if includeExamples
108114
then basePlugins ++ examplePlugins
@@ -170,7 +176,7 @@ idePlugins includeExamples = pluginDescToIdePlugins allPlugins
170176
#endif
171177
-- The ghcide descriptors should come last so that the notification handlers
172178
-- (which restart the Shake build) run after everything else
173-
GhcIde.descriptors
179+
GhcIde.descriptors (cmap LogGhcide recorder)
174180
examplePlugins =
175181
[Example.descriptor "eg"
176182
,Example2.descriptor "eg2"

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

Lines changed: 11 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,7 @@ module Development.IDE.Core.Service(
1515
getDiagnostics,
1616
ideLogger,
1717
updatePositionMapping,
18+
Log
1819
) where
1920

2021
import Control.Applicative ((<|>))
@@ -29,16 +30,22 @@ import qualified Language.LSP.Server as LSP
2930
import qualified Language.LSP.Types as LSP
3031

3132
import Control.Monad
32-
import Development.IDE.Core.Shake
33+
import Development.IDE.Core.Shake hiding (Log)
34+
import qualified Development.IDE.Core.Shake as Shake
3335
import Development.IDE.Types.Shake (WithHieDb)
3436
import System.Environment (lookupEnv)
3537

3638

39+
data Log
40+
= LogShake Shake.Log
41+
deriving Show
42+
3743
------------------------------------------------------------
3844
-- Exposed API
3945

4046
-- | Initialise the Compiler Service.
41-
initialise :: Config
47+
initialise :: Recorder Log
48+
-> Config
4249
-> Rules ()
4350
-> Maybe (LSP.LanguageContextEnv Config)
4451
-> Logger
@@ -48,12 +55,13 @@ initialise :: Config
4855
-> WithHieDb
4956
-> IndexQueue
5057
-> IO IdeState
51-
initialise defaultConfig mainRule lspEnv logger debouncer options vfs withHieDb hiedbChan = do
58+
initialise recorder defaultConfig mainRule lspEnv logger debouncer options vfs withHieDb hiedbChan = do
5259
shakeProfiling <- do
5360
let fromConf = optShakeProfiling options
5461
fromEnv <- lookupEnv "GHCIDE_BUILD_PROFILING"
5562
return $ fromConf <|> fromEnv
5663
shakeOpen
64+
(cmap LogShake recorder)
5765
lspEnv
5866
defaultConfig
5967
logger

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

Lines changed: 42 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -77,6 +77,7 @@ module Development.IDE.Core.Shake(
7777
addPersistentRule,
7878
garbageCollectDirtyKeys,
7979
garbageCollectDirtyKeysOlderThan,
80+
Log
8081
) where
8182

8283
import Control.Concurrent.Async
@@ -149,6 +150,7 @@ import Language.LSP.Types.Capabilities
149150
import OpenTelemetry.Eventlog
150151

151152
import Control.Concurrent.STM.Stats (atomicallyNamed)
153+
import Control.Exception.Base (SomeException (SomeException))
152154
import Control.Exception.Extra hiding (bracket_)
153155
import Data.Aeson (toJSON)
154156
import qualified Data.ByteString.Char8 as BS8
@@ -160,6 +162,7 @@ import qualified Data.HashSet as HSet
160162
import Data.String (fromString)
161163
import Data.Text (pack)
162164
import Debug.Trace.Flags (userTracingEnabled)
165+
import Development.IDE.Types.Action (DelayedActionInternal)
163166
import qualified Development.IDE.Types.Exports as ExportsMap
164167
import qualified Focus
165168
import HieDb.Types
@@ -169,6 +172,16 @@ import Ide.Types (PluginId)
169172
import qualified "list-t" ListT
170173
import qualified StmContainers.Map as STM
171174

175+
data Log
176+
= LogCreateHieDbExportsMapStart
177+
-- logDebug logger "Initializing exports map from hiedb"
178+
| LogCreateHieDbExportsMapFinish !Int
179+
-- logDebug logger $ "Done initializing exports map from hiedb (" <> pack(show (ExportsMap.size em)) <> ")"
180+
| LogBuildSessionRestart !String ![DelayedActionInternal] !(HashSet Key) !Seconds !(Maybe FilePath)
181+
| LogDelayedAction !(DelayedAction ()) !Seconds
182+
| LogBuildSessionFinish !(Maybe SomeException)
183+
deriving Show
184+
172185
-- | We need to serialize writes to the database, so we send any function that
173186
-- needs to write to the database over the channel, where it will be picked up by
174187
-- a worker thread.
@@ -494,7 +507,8 @@ seqValue val = case val of
494507
Failed _ -> val
495508

496509
-- | Open a 'IdeState', should be shut using 'shakeShut'.
497-
shakeOpen :: Maybe (LSP.LanguageContextEnv Config)
510+
shakeOpen :: Recorder Log
511+
-> Maybe (LSP.LanguageContextEnv Config)
498512
-> Config
499513
-> Logger
500514
-> Debouncer NormalizedUri
@@ -507,8 +521,10 @@ shakeOpen :: Maybe (LSP.LanguageContextEnv Config)
507521
-> ShakeOptions
508522
-> Rules ()
509523
-> IO IdeState
510-
shakeOpen lspEnv defaultConfig logger debouncer
524+
shakeOpen recorder lspEnv defaultConfig logger debouncer
511525
shakeProfileDir (IdeReportProgress reportProgress) ideTesting@(IdeTesting testing) withHieDb indexQueue vfs opts rules = mdo
526+
let log :: Log -> IO ()
527+
log = logWith recorder
512528

513529
us <- mkSplitUniqSupply 'r'
514530
ideNc <- newIORef (initNameCache us knownKeyNames)
@@ -520,19 +536,20 @@ shakeOpen lspEnv defaultConfig logger debouncer
520536
publishedDiagnostics <- STM.newIO
521537
positionMapping <- STM.newIO
522538
knownTargetsVar <- newTVarIO $ hashed HMap.empty
523-
let restartShakeSession = shakeRestart ideState
539+
let restartShakeSession = shakeRestart recorder ideState
524540
persistentKeys <- newTVarIO HMap.empty
525541
indexPending <- newTVarIO HMap.empty
526542
indexCompleted <- newTVarIO 0
527543
indexProgressToken <- newVar Nothing
528544
let hiedbWriter = HieDbWriter{..}
529545
exportsMap <- newTVarIO mempty
530546
-- lazily initialize the exports map with the contents of the hiedb
547+
-- TODO: exceptions can be swallowed here?
531548
_ <- async $ do
532-
logDebug logger "Initializing exports map from hiedb"
549+
log LogCreateHieDbExportsMapStart
533550
em <- createExportsMapHieDb withHieDb
534551
atomically $ modifyTVar' exportsMap (<> em)
535-
logDebug logger $ "Done initializing exports map from hiedb (" <> pack(show (ExportsMap.size em)) <> ")"
552+
log $ LogCreateHieDbExportsMapFinish (ExportsMap.size em)
536553

537554
progress <- do
538555
let (before, after) = if testing then (0,0.1) else (0.1,0.1)
@@ -584,9 +601,9 @@ startTelemetry db extras@ShakeExtras{..}
584601

585602

586603
-- | Must be called in the 'Initialized' handler and only once
587-
shakeSessionInit :: IdeState -> IO ()
588-
shakeSessionInit ide@IdeState{..} = do
589-
initSession <- newSession shakeExtras shakeDb [] "shakeSessionInit"
604+
shakeSessionInit :: Recorder Log -> IdeState -> IO ()
605+
shakeSessionInit recorder ide@IdeState{..} = do
606+
initSession <- newSession recorder shakeExtras shakeDb [] "shakeSessionInit"
590607
putMVar shakeSession initSession
591608
logDebug (ideLogger ide) "Shake session initialized"
592609

@@ -626,15 +643,19 @@ delayedAction a = do
626643
-- | Restart the current 'ShakeSession' with the given system actions.
627644
-- Any actions running in the current session will be aborted,
628645
-- but actions added via 'shakeEnqueue' will be requeued.
629-
shakeRestart :: IdeState -> String -> [DelayedAction ()] -> IO ()
630-
shakeRestart IdeState{..} reason acts =
646+
shakeRestart :: Recorder Log -> IdeState -> String -> [DelayedAction ()] -> IO ()
647+
shakeRestart recorder IdeState{..} reason acts =
631648
withMVar'
632649
shakeSession
633650
(\runner -> do
651+
let log = logWith recorder
634652
(stopTime,()) <- duration (cancelShakeSession runner)
635653
res <- shakeDatabaseProfile shakeDb
636654
backlog <- readTVarIO $ dirtyKeys shakeExtras
637655
queue <- atomicallyNamed "actionQueue - peek" $ peekInProgress $ actionQueue shakeExtras
656+
657+
log $ LogBuildSessionRestart reason queue backlog stopTime res
658+
638659
let profile = case res of
639660
Just fp -> ", profile saved at " <> fp
640661
_ -> ""
@@ -643,14 +664,13 @@ shakeRestart IdeState{..} reason acts =
643664
queueMsg = " with queue " ++ show (map actionName queue)
644665
keysMsg = " for keys " ++ show (HSet.toList backlog) ++ " "
645666
abortMsg = "(aborting the previous one took " ++ showDuration stopTime ++ profile ++ ")"
646-
logDebug (logger shakeExtras) msg
647667
notifyTestingLogMessage shakeExtras msg
648668
)
649669
-- It is crucial to be masked here, otherwise we can get killed
650670
-- between spawning the new thread and updating shakeSession.
651671
-- See https://github.com/haskell/ghcide/issues/79
652672
(\() -> do
653-
(,()) <$> newSession shakeExtras shakeDb acts reason)
673+
(,()) <$> newSession recorder shakeExtras shakeDb acts reason)
654674

655675
notifyTestingLogMessage :: ShakeExtras -> T.Text -> IO ()
656676
notifyTestingLogMessage extras msg = do
@@ -684,12 +704,13 @@ shakeEnqueue ShakeExtras{actionQueue, logger} act = do
684704
-- | Set up a new 'ShakeSession' with a set of initial actions
685705
-- Will crash if there is an existing 'ShakeSession' running.
686706
newSession
687-
:: ShakeExtras
707+
:: Recorder Log
708+
-> ShakeExtras
688709
-> ShakeDatabase
689710
-> [DelayedActionInternal]
690711
-> String
691712
-> IO ShakeSession
692-
newSession extras@ShakeExtras{..} shakeDb acts reason = do
713+
newSession recorder extras@ShakeExtras{..} shakeDb acts reason = do
693714
IdeOptions{optRunSubset} <- getIdeOptionsIO extras
694715
reenqueued <- atomicallyNamed "actionQueue - peek" $ peekInProgress actionQueue
695716
allPendingKeys <-
@@ -712,7 +733,7 @@ newSession extras@ShakeExtras{..} shakeDb acts reason = do
712733
let msg = T.pack $ "finish: " ++ actionName d
713734
++ " (took " ++ showDuration runTime ++ ")"
714735
liftIO $ do
715-
logPriority logger (actionPriority d) msg
736+
logWith recorder $ LogDelayedAction d runTime
716737
notifyTestingLogMessage extras msg
717738

718739
-- The inferred type signature doesn't work in ghc >= 9.0.1
@@ -729,14 +750,19 @@ newSession extras@ShakeExtras{..} shakeDb acts reason = do
729750
Right _ -> "completed"
730751
let msg = T.pack $ "Finishing build session(" ++ res' ++ ")"
731752
return $ do
732-
logDebug logger msg
753+
let exception =
754+
case res of
755+
Left e -> Just e
756+
_ -> Nothing
757+
logWith recorder $ LogBuildSessionFinish exception
733758
notifyTestingLogMessage extras msg
734759

735760
-- Do the work in a background thread
736761
workThread <- asyncWithUnmask workRun
737762

738763
-- run the wrap up in a separate thread since it contains interruptible
739764
-- commands (and we are not using uninterruptible mask)
765+
-- TODO: can possibly swallow exceptions?
740766
_ <- async $ join $ wait workThread
741767

742768
-- Cancelling is required to flush the Shake database when either

ghcide/src/Development/IDE/LSP/Notifications.hs

Lines changed: 11 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@
99
module Development.IDE.LSP.Notifications
1010
( whenUriFile
1111
, descriptor
12+
, Log
1213
) where
1314

1415
import Language.LSP.Types
@@ -29,18 +30,23 @@ import Development.IDE.Core.FileStore (registerFileWatches,
2930
import Development.IDE.Core.IdeConfiguration
3031
import Development.IDE.Core.OfInterest
3132
import Development.IDE.Core.RuleTypes (GetClientSettings (..))
32-
import Development.IDE.Core.Service
33-
import Development.IDE.Core.Shake
33+
import Development.IDE.Core.Service hiding (Log)
34+
import Development.IDE.Core.Shake hiding (Log)
35+
import qualified Development.IDE.Core.Shake as Shake
3436
import Development.IDE.Types.Location
3537
import Development.IDE.Types.Logger
3638
import Development.IDE.Types.Shake (toKey)
3739
import Ide.Types
3840

41+
data Log
42+
= LogShake Shake.Log
43+
deriving Show
44+
3945
whenUriFile :: Uri -> (NormalizedFilePath -> IO ()) -> IO ()
4046
whenUriFile uri act = whenJust (LSP.uriToFilePath uri) $ act . toNormalizedFilePath'
4147

42-
descriptor :: PluginId -> PluginDescriptor IdeState
43-
descriptor plId = (defaultPluginDescriptor plId) { pluginNotificationHandlers = mconcat
48+
descriptor :: Recorder Log -> PluginId -> PluginDescriptor IdeState
49+
descriptor recorder plId = (defaultPluginDescriptor plId) { pluginNotificationHandlers = mconcat
4450
[ mkPluginNotificationHandler LSP.STextDocumentDidOpen $
4551
\ide _ (DidOpenTextDocumentParams TextDocumentItem{_uri,_version}) -> liftIO $ do
4652
atomically $ updatePositionMapping ide (VersionedTextDocumentIdentifier _uri (Just _version)) (List [])
@@ -112,7 +118,7 @@ descriptor plId = (defaultPluginDescriptor plId) { pluginNotificationHandlers =
112118

113119
, mkPluginNotificationHandler LSP.SInitialized $ \ide _ _ -> do
114120
--------- Initialize Shake session --------------------------------------------------------------------
115-
liftIO $ shakeSessionInit ide
121+
liftIO $ shakeSessionInit (cmap LogShake recorder) ide
116122

117123
--------- Set up file watchers ------------------------------------------------------------------------
118124
opts <- liftIO $ getIdeOptionsIO $ shakeExtras ide

0 commit comments

Comments
 (0)