Skip to content

Commit 9e1738e

Browse files
authored
Fix DisplayTHWarning error (#2895)
This used to fail in the CLI with ``` Internal error, getIdeGlobalExtras, no entry for DisplayTHWarning ```
1 parent 6524122 commit 9e1738e

File tree

2 files changed

+22
-15
lines changed

2 files changed

+22
-15
lines changed

Diff for: ghcide/src/Development/IDE/Core/Rules.hs

+13-6
Original file line numberDiff line numberDiff line change
@@ -835,9 +835,13 @@ instance IsIdeGlobal DisplayTHWarning
835835
getModSummaryRule :: LspT Config IO () -> Recorder (WithPriority Log) -> Rules ()
836836
getModSummaryRule displayTHWarning recorder = do
837837
menv <- lspEnv <$> getShakeExtrasRules
838-
forM_ menv $ \env -> do
838+
case menv of
839+
Just env -> do
839840
displayItOnce <- liftIO $ once $ LSP.runLspT env displayTHWarning
840841
addIdeGlobal (DisplayTHWarning displayItOnce)
842+
Nothing -> do
843+
logItOnce <- liftIO $ once $ putStrLn ""
844+
addIdeGlobal (DisplayTHWarning logItOnce)
841845

842846
defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \GetModSummary f -> do
843847
session' <- hscEnv <$> use_ GhcSession f
@@ -1118,13 +1122,16 @@ instance Default RulesConfig where
11181122
displayTHWarning
11191123
| not isWindows && not hostIsDynamic = do
11201124
LSP.sendNotification SWindowShowMessage $
1121-
ShowMessageParams MtInfo $ T.unwords
1122-
[ "This HLS binary does not support Template Haskell."
1123-
, "Follow the [instructions](" <> templateHaskellInstructions <> ")"
1124-
, "to build an HLS binary with support for Template Haskell."
1125-
]
1125+
ShowMessageParams MtInfo thWarningMessage
11261126
| otherwise = return ()
11271127

1128+
thWarningMessage :: T.Text
1129+
thWarningMessage = T.unwords
1130+
[ "This HLS binary does not support Template Haskell."
1131+
, "Follow the [instructions](" <> templateHaskellInstructions <> ")"
1132+
, "to build an HLS binary with support for Template Haskell."
1133+
]
1134+
11281135
-- | A rule that wires per-file rules together
11291136
mainRule :: Recorder (WithPriority Log) -> RulesConfig -> Rules ()
11301137
mainRule recorder RulesConfig{..} = do

Diff for: ghcide/src/Development/IDE/Core/Shake.hs

+9-9
Original file line numberDiff line numberDiff line change
@@ -99,10 +99,10 @@ import Data.EnumMap.Strict (EnumMap)
9999
import qualified Data.EnumMap.Strict as EM
100100
import Data.Foldable (for_, toList)
101101
import Data.Functor ((<&>))
102+
import Data.Hashable
102103
import qualified Data.HashMap.Strict as HMap
103104
import Data.HashSet (HashSet)
104105
import qualified Data.HashSet as HSet
105-
import Data.Hashable
106106
import Data.IORef
107107
import Data.List.Extra (foldl', partition,
108108
takeEnd)
@@ -148,12 +148,12 @@ import Development.IDE.Types.KnownTargets
148148
import Development.IDE.Types.Location
149149
import Development.IDE.Types.Logger hiding (Priority)
150150
import qualified Development.IDE.Types.Logger as Logger
151+
import Development.IDE.Types.Monitoring (Monitoring (..))
151152
import Development.IDE.Types.Options
152153
import Development.IDE.Types.Shake
153154
import qualified Focus
154155
import GHC.Fingerprint
155-
import Language.LSP.Types.Capabilities
156-
import OpenTelemetry.Eventlog
156+
import GHC.Stack (HasCallStack)
157157
import HieDb.Types
158158
import Ide.Plugin.Config
159159
import qualified Ide.PluginUtils as HLS
@@ -162,13 +162,14 @@ import Language.LSP.Diagnostics
162162
import qualified Language.LSP.Server as LSP
163163
import Language.LSP.Types
164164
import qualified Language.LSP.Types as LSP
165+
import Language.LSP.Types.Capabilities
165166
import Language.LSP.VFS
166167
import qualified "list-t" ListT
168+
import OpenTelemetry.Eventlog
167169
import qualified StmContainers.Map as STM
168170
import System.FilePath hiding (makeRelative)
169-
import System.IO.Unsafe (unsafePerformIO)
171+
import System.IO.Unsafe (unsafePerformIO)
170172
import System.Time.Extra
171-
import Development.IDE.Types.Monitoring (Monitoring(..))
172173

173174
data Log
174175
= LogCreateHieDbExportsMapStart
@@ -341,7 +342,7 @@ addIdeGlobalExtras ShakeExtras{globals} x@(typeOf -> ty) =
341342
Just _ -> error $ "Internal error, addIdeGlobalExtras, got the same type twice for " ++ show ty
342343
Nothing -> HMap.insert ty (toDyn x) mp
343344

344-
getIdeGlobalExtras :: forall a . IsIdeGlobal a => ShakeExtras -> IO a
345+
getIdeGlobalExtras :: forall a . (HasCallStack, IsIdeGlobal a) => ShakeExtras -> IO a
345346
getIdeGlobalExtras ShakeExtras{globals} = do
346347
let typ = typeRep (Proxy :: Proxy a)
347348
x <- HMap.lookup (typeRep (Proxy :: Proxy a)) <$> readTVarIO globals
@@ -351,13 +352,12 @@ getIdeGlobalExtras ShakeExtras{globals} = do
351352
| otherwise -> errorIO $ "Internal error, getIdeGlobalExtras, wrong type for " ++ show typ ++ " (got " ++ show (dynTypeRep x) ++ ")"
352353
Nothing -> errorIO $ "Internal error, getIdeGlobalExtras, no entry for " ++ show typ
353354

354-
getIdeGlobalAction :: forall a . IsIdeGlobal a => Action a
355+
getIdeGlobalAction :: forall a . (HasCallStack, IsIdeGlobal a) => Action a
355356
getIdeGlobalAction = liftIO . getIdeGlobalExtras =<< getShakeExtras
356357

357358
getIdeGlobalState :: forall a . IsIdeGlobal a => IdeState -> IO a
358359
getIdeGlobalState = getIdeGlobalExtras . shakeExtras
359360

360-
361361
newtype GlobalIdeOptions = GlobalIdeOptions IdeOptions
362362
instance IsIdeGlobal GlobalIdeOptions
363363

@@ -756,7 +756,7 @@ newSession recorder extras@ShakeExtras{..} vfsMod shakeDb acts reason = do
756756

757757
-- Take a new VFS snapshot
758758
case vfsMod of
759-
VFSUnmodified -> pure ()
759+
VFSUnmodified -> pure ()
760760
VFSModified vfs -> atomically $ writeTVar vfsVar vfs
761761

762762
IdeOptions{optRunSubset} <- getIdeOptionsIO extras

0 commit comments

Comments
 (0)