Skip to content

Commit

Permalink
Revert "Warn if TH and Mac and static binary (haskell#2470)"
Browse files Browse the repository at this point in the history
This reverts commit 807cb8f.
  • Loading branch information
jneira committed Feb 28, 2022
1 parent 451a9e6 commit c7112e5
Show file tree
Hide file tree
Showing 2 changed files with 13 additions and 42 deletions.
12 changes: 7 additions & 5 deletions docs/troubleshooting.md
Original file line number Diff line number Diff line change
Expand Up @@ -63,13 +63,15 @@ Often this means that the client is configured to run the wrong binary, or the c

The easiest way to check whether the server is running is to use an OS process monitor to see if there is a `haskell-language-server` process running.

### Checking whether the client is connecting to the server
### Problems with Template Haskell

If the server is running, you should see some kind of indicator in your client.
In some clients (e.g. `coc`) you may need to run a command to query the client's beliefs about the server state.
If the client doesn't seem to be connected despite the server running, this may indicate a bug in the client or HLS.
Due to how Template Haskell code is evaluated at compile time and some limitations in the interaction between HLS and GHC, the loading of modules using TH can be problematic.

### Checking whether the project is being built correctly by HLS
The errors thrown are usually related to linking and usually make HLS crash: `Segmentation fault`, `GHC runtime linker: fatal error`, etc

A workaround which has helped in some cases is to compile HLS from source with the ghc option `-dynamic` enabled, as in the previous issue.

We have a [dedicated label](https://github.com/haskell/haskell-language-server/issues?q=is%3Aissue+is%3Aopen+label%3A%22type%3A+template+haskell+related%22) in the issue tracker and an [general issue](https://github.com/haskell/haskell-language-server/issues/1431) tracking support for TH.

HLS needs to build the project correctly, with the correct flags, and if it does not do so then very little is likely to work.
A typical symptom of this going wrong is "incorrect" compilation errors being sent to the client.
Expand Down
43 changes: 6 additions & 37 deletions ghcide/src/Development/IDE/Core/Rules.hs
Original file line number Diff line number Diff line change
Expand Up @@ -57,8 +57,7 @@ module Development.IDE.Core.Rules(
getParsedModuleDefinition,
typeCheckRuleDefinition,
GhcSessionDepsConfig(..),
Log(..),
DisplayTHWarning(..),
Log(..)
) where

#if !MIN_VERSION_ghc(8,8,0)
Expand Down Expand Up @@ -136,7 +135,7 @@ import qualified GHC.LanguageExtensions as LangExt
import qualified HieDb
import Ide.Plugin.Config
import qualified Language.LSP.Server as LSP
import Language.LSP.Types (SMethod (SCustomMethod, SWindowShowMessage), ShowMessageParams (ShowMessageParams), MessageType (MtInfo))
import Language.LSP.Types (SMethod (SCustomMethod))
import Language.LSP.VFS
import System.Directory (makeAbsolute)
import Data.Default (def, Default)
Expand All @@ -149,15 +148,12 @@ import Ide.PluginUtils (configForPlugin)
import Ide.Types (DynFlagsModifications (dynFlagsModifyGlobal, dynFlagsModifyParser),
PluginId)
import Control.Concurrent.STM.Stats (atomically)
import Language.LSP.Server (LspT)
import System.Info.Extra (isWindows)
import HIE.Bios.Ghc.Gap (hostIsDynamic)
import Development.IDE.Types.Logger (Recorder, logWith, cmapWithPrio, WithPriority, Pretty (pretty), (<+>), nest, vcat)
import qualified Development.IDE.Core.Shake as Shake
import qualified Development.IDE.GHC.ExactPrint as ExactPrint hiding (LogShake)
import qualified Development.IDE.Types.Logger as Logger

data Log
data Log
= LogShake Shake.Log
| LogReindexingHieFile !NormalizedFilePath
| LogLoadingHieFile !NormalizedFilePath
Expand All @@ -182,9 +178,6 @@ instance Pretty Log where
"SUCCEEDED LOADING HIE FILE FOR" <+> pretty path
LogExactPrint log -> pretty log

templateHaskellInstructions :: T.Text
templateHaskellInstructions = "https://haskell-language-server.readthedocs.io/en/latest/troubleshooting.html#static-binaries"

-- | This is useful for rules to convert rules that can only produce errors or
-- a result into the more general IdeResult type that supports producing
-- warnings while also producing a result.
Expand Down Expand Up @@ -852,27 +845,8 @@ isHiFileStableRule recorder = defineEarlyCutoff (cmapWithPrio LogShake recorder)
summarize SourceUnmodified = BS.singleton 2
summarize SourceUnmodifiedAndStable = BS.singleton 3

displayTHWarning :: LspT c IO ()
displayTHWarning
| not isWindows && not hostIsDynamic = do
LSP.sendNotification SWindowShowMessage $
ShowMessageParams MtInfo $ T.unwords
[ "This HLS binary does not support Template Haskell."
, "Follow the [instructions](" <> templateHaskellInstructions <> ")"
, "to build an HLS binary with support for Template Haskell."
]
| otherwise = return ()

newtype DisplayTHWarning = DisplayTHWarning (IO ())
instance IsIdeGlobal DisplayTHWarning

getModSummaryRule :: Recorder (WithPriority Log) -> Rules ()
getModSummaryRule recorder = do
menv <- lspEnv <$> getShakeExtrasRules
forM_ menv $ \env -> do
displayItOnce <- liftIO $ once $ LSP.runLspT env displayTHWarning
addIdeGlobal (DisplayTHWarning displayItOnce)

defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \GetModSummary f -> do
session' <- hscEnv <$> use_ GhcSession f
modify_dflags <- getModifyDynFlags dynFlagsModifyGlobal
Expand All @@ -883,10 +857,6 @@ getModSummaryRule recorder = do
getModSummaryFromImports session fp modTime (textToStringBuffer <$> mFileContent)
case modS of
Right res -> do
-- Check for Template Haskell
when (uses_th_qq $ msrModSummary res) $ do
DisplayTHWarning act <- getIdeGlobalAction
liftIO act
bufFingerPrint <- liftIO $
fingerprintFromStringBuffer $ fromJust $ ms_hspp_buf $ msrModSummary res
let fingerPrint = Util.fingerprintFingerprints
Expand Down Expand Up @@ -1082,6 +1052,9 @@ needsCompilationRule file = do

pure (Just $ encodeLinkableType res, Just res)
where
uses_th_qq (ms_hspp_opts -> dflags) =
xopt LangExt.TemplateHaskell dflags || xopt LangExt.QuasiQuotes dflags

computeLinkableType :: ModSummary -> [Maybe ModSummary] -> [Maybe LinkableType] -> Maybe LinkableType
computeLinkableType this deps xs
| Just ObjectLinkable `elem` xs = Just ObjectLinkable -- If any dependent needs object code, so do we
Expand All @@ -1091,10 +1064,6 @@ needsCompilationRule file = do
where
this_type = computeLinkableTypeForDynFlags (ms_hspp_opts this)

uses_th_qq :: ModSummary -> Bool
uses_th_qq (ms_hspp_opts -> dflags) =
xopt LangExt.TemplateHaskell dflags || xopt LangExt.QuasiQuotes dflags

-- | How should we compile this module?
-- (assuming we do in fact need to compile it).
-- Depends on whether it uses unboxed tuples or sums
Expand Down

0 comments on commit c7112e5

Please sign in to comment.