Skip to content

Commit

Permalink
Merge branch 'master' into test-temp-dir
Browse files Browse the repository at this point in the history
  • Loading branch information
komikat authored Aug 19, 2024
2 parents 0df9923 + 6f6f75b commit 507dac7
Show file tree
Hide file tree
Showing 29 changed files with 1,007 additions and 177 deletions.
8 changes: 7 additions & 1 deletion docs/features.md
Original file line number Diff line number Diff line change
Expand Up @@ -111,6 +111,7 @@ Completions for language pragmas.
## Formatting

Format your code with various Haskell code formatters.
The default Haskell code formatter is `ormolu`, and the Haskell formatter can be configured via the `formattingProvider` option.

| Formatter | Provided by |
| --------------- | ---------------------------- |
Expand All @@ -119,12 +120,17 @@ Format your code with various Haskell code formatters.
| Ormolu | `hls-ormolu-plugin` |
| Stylish Haskell | `hls-stylish-haskell-plugin` |

---

Format your cabal files with a cabal code formatter.
The default cabal code formatter is `cabal-gild`, which needs to be available on the `$PATH`,
or the location needs to be explicitly provided.
To change the cabal formatter, edit the `cabalFormattingProvider` option.

| Formatter | Provided by |
|-----------------|------------------------------|
| cabal-fmt | `hls-cabal-fmt-plugin` |

| cabal-gild | `hls-cabal-gild-plugin` |

## Document symbols

Expand Down
1 change: 1 addition & 0 deletions ghcide/src/Development/IDE/Core/OfInterest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,7 @@ import Development.IDE.Graph
import Control.Concurrent.STM.Stats (atomically,
modifyTVar')
import Data.Aeson (toJSON)
import qualified Data.Aeson as Aeson
import qualified Data.ByteString as BS
import Data.Maybe (catMaybes)
import Development.IDE.Core.ProgressReporting
Expand Down
39 changes: 29 additions & 10 deletions ghcide/src/Development/IDE/Core/Shake.hs
Original file line number Diff line number Diff line change
Expand Up @@ -73,7 +73,8 @@ module Development.IDE.Core.Shake(
garbageCollectDirtyKeysOlderThan,
Log(..),
VFSModified(..), getClientConfigAction,
ThreadQueue(..)
ThreadQueue(..),
runWithSignal
) where

import Control.Concurrent.Async
Expand Down Expand Up @@ -123,6 +124,10 @@ import Development.IDE.Core.FileUtils (getModTime)
import Development.IDE.Core.PositionMapping
import Development.IDE.Core.ProgressReporting
import Development.IDE.Core.RuleTypes
import Development.IDE.Types.Options as Options
import qualified Language.LSP.Protocol.Message as LSP
import qualified Language.LSP.Server as LSP

import Development.IDE.Core.Tracing
import Development.IDE.Core.WorkerThread
import Development.IDE.GHC.Compat (NameCache,
Expand All @@ -147,11 +152,11 @@ import qualified Development.IDE.Types.Exports as ExportsMap
import Development.IDE.Types.KnownTargets
import Development.IDE.Types.Location
import Development.IDE.Types.Monitoring (Monitoring (..))
import Development.IDE.Types.Options
import Development.IDE.Types.Shake
import qualified Focus
import GHC.Fingerprint
import GHC.Stack (HasCallStack)
import GHC.TypeLits (KnownSymbol)
import HieDb.Types
import Ide.Logger hiding (Priority)
import qualified Ide.Logger as Logger
Expand All @@ -165,7 +170,6 @@ import qualified Language.LSP.Protocol.Lens as L
import Language.LSP.Protocol.Message
import Language.LSP.Protocol.Types
import qualified Language.LSP.Protocol.Types as LSP
import qualified Language.LSP.Server as LSP
import Language.LSP.VFS hiding (start)
import qualified "list-t" ListT
import OpenTelemetry.Eventlog hiding (addEvent)
Expand Down Expand Up @@ -1350,29 +1354,28 @@ updateFileDiagnostics recorder fp ver k ShakeExtras{diagnostics, hiddenDiagnosti
let uri' = filePathToUri' fp
let delay = if null newDiags then 0.1 else 0
registerEvent debouncer delay uri' $ withTrace ("report diagnostics " <> fromString (fromNormalizedFilePath fp)) $ \tag -> do
join $ mask_ $ do
lastPublish <- atomicallyNamed "diagnostics - publish" $ STM.focus (Focus.lookupWithDefault [] <* Focus.insert newDiags) uri' publishedDiagnostics
let action = when (lastPublish /= newDiags) $ case lspEnv of
join $ mask_ $ do
lastPublish <- atomicallyNamed "diagnostics - publish" $ STM.focus (Focus.lookupWithDefault [] <* Focus.insert newDiags) uri' publishedDiagnostics
let action = when (lastPublish /= newDiags) $ case lspEnv of
Nothing -> -- Print an LSP event.
logWith recorder Info $ LogDiagsDiffButNoLspEnv (map (fp, ShowDiag,) newDiags)
Just env -> LSP.runLspT env $ do
liftIO $ tag "count" (show $ Prelude.length newDiags)
liftIO $ tag "key" (show k)
LSP.sendNotification SMethod_TextDocumentPublishDiagnostics $
LSP.PublishDiagnosticsParams (fromNormalizedUri uri') (fmap fromIntegral ver) newDiags
return action
return action
where
diagsFromRule :: Diagnostic -> Diagnostic
diagsFromRule c@Diagnostic{_range}
| coerce ideTesting = c & L.relatedInformation ?~
[
DiagnosticRelatedInformation
[ DiagnosticRelatedInformation
(Location
(filePathToUri $ fromNormalizedFilePath fp)
_range
)
(T.pack $ show k)
]
]
| otherwise = c


Expand Down Expand Up @@ -1444,3 +1447,19 @@ updatePositionMappingHelper ver changes mappingForUri = snd $
EM.mapAccumRWithKey (\acc _k (delta, _) -> let new = addOldDelta delta acc in (new, (delta, acc)))
zeroMapping
(EM.insert ver (mkDelta changes, zeroMapping) mappingForUri)

-- | sends a signal whenever shake session is run/restarted
-- being used in cabal and hlint plugin tests to know when its time
-- to look for file diagnostics
kickSignal :: KnownSymbol s => Bool -> Maybe (LSP.LanguageContextEnv c) -> [NormalizedFilePath] -> Proxy s -> Action ()
kickSignal testing lspEnv files msg = when testing $ liftIO $ mRunLspT lspEnv $
LSP.sendNotification (LSP.SMethod_CustomMethod msg) $
toJSON $ map fromNormalizedFilePath files

-- | Add kick start/done signal to rule
runWithSignal :: (KnownSymbol s0, KnownSymbol s1, IdeRule k v) => Proxy s0 -> Proxy s1 -> [NormalizedFilePath] -> k -> Action ()
runWithSignal msgStart msgEnd files rule = do
ShakeExtras{ideTesting = Options.IdeTesting testing, lspEnv} <- getShakeExtras
kickSignal testing lspEnv files msgStart
void $ uses rule files
kickSignal testing lspEnv files msgEnd
7 changes: 6 additions & 1 deletion haskell-language-server.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -242,8 +242,10 @@ library hls-cabal-plugin
Ide.Plugin.Cabal.Completion.Completions
Ide.Plugin.Cabal.Completion.Data
Ide.Plugin.Cabal.Completion.Types
Ide.Plugin.Cabal.FieldSuggest
Ide.Plugin.Cabal.LicenseSuggest
Ide.Plugin.Cabal.Orphans
Ide.Plugin.Cabal.Outline
Ide.Plugin.Cabal.Parse


Expand Down Expand Up @@ -281,10 +283,12 @@ test-suite hls-cabal-plugin-tests
Completer
Context
Utils
Outline
build-depends:
, base
, bytestring
, Cabal-syntax >= 3.7
, extra
, filepath
, ghcide
, haskell-language-server:hls-cabal-plugin
Expand Down Expand Up @@ -712,7 +716,6 @@ library hls-hlint-plugin
, hlint >= 3.5 && < 3.9
, hls-plugin-api == 2.9.0.1
, lens
, lsp
, mtl
, refact
, regex-tdfa
Expand All @@ -723,6 +726,8 @@ library hls-hlint-plugin
, unordered-containers
, ghc-lib-parser-ex
, apply-refact
--
, lsp-types

if flag(ghc-lib)
cpp-options: -DGHC_LIB
Expand Down
27 changes: 22 additions & 5 deletions hls-test-utils/src/Test/Hls.hs
Original file line number Diff line number Diff line change
Expand Up @@ -61,14 +61,17 @@ module Test.Hls
WithPriority(..),
Recorder,
Priority(..),
TestConfig(..),
captureKickDiagnostics,
kick,
TestConfig(..)
)
where

import Control.Applicative.Combinators
import Control.Concurrent.Async (async, cancel, wait)
import Control.Concurrent.Extra
import Control.Exception.Safe
import Control.Lens ((^.))
import Control.Lens.Extras (is)
import Control.Monad (guard, unless, void)
import Control.Monad.Extra (forM)
Expand All @@ -80,7 +83,7 @@ import qualified Data.Aeson as A
import Data.ByteString.Lazy (ByteString)
import Data.Default (Default, def)
import qualified Data.Map as M
import Data.Maybe (fromMaybe)
import Data.Maybe (fromMaybe, mapMaybe)
import Data.Proxy (Proxy (Proxy))
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
Expand Down Expand Up @@ -114,6 +117,7 @@ import Ide.PluginUtils (idePluginsToPluginDes
pluginDescToIdePlugins)
import Ide.Types
import Language.LSP.Protocol.Capabilities
import qualified Language.LSP.Protocol.Lens as L
import Language.LSP.Protocol.Message
import qualified Language.LSP.Protocol.Message as LSP
import Language.LSP.Protocol.Types hiding (Null)
Expand Down Expand Up @@ -232,14 +236,14 @@ goldenWithTestConfig
:: Pretty b
=> TestConfig b
-> TestName
-> FilePath
-> VirtualFileTree
-> FilePath
-> FilePath
-> FilePath
-> (TextDocumentIdentifier -> Session ())
-> TestTree
goldenWithTestConfig config title testDataDir path desc ext act =
goldenGitDiff title (testDataDir </> path <.> desc <.> ext)
goldenWithTestConfig config title tree path desc ext act =
goldenGitDiff title (vftOriginalRoot tree </> path <.> desc <.> ext)
$ runSessionWithTestConfig config $ const
$ TL.encodeUtf8 . TL.fromStrict
<$> do
Expand Down Expand Up @@ -870,6 +874,17 @@ setHlsConfig config = do
-- requests!
skipManyTill anyMessage (void configurationRequest)

captureKickDiagnostics :: Session () -> Session () -> Session [Diagnostic]
captureKickDiagnostics start done = do
_ <- skipManyTill anyMessage start
messages <- manyTill anyMessage done
pure $ concat $ mapMaybe diagnostics messages
where
diagnostics :: FromServerMessage' a -> Maybe [Diagnostic]
diagnostics = \msg -> case msg of
FromServerMess SMethod_TextDocumentPublishDiagnostics diags -> Just (diags ^. L.params . L.diagnostics)
_ -> Nothing

waitForKickDone :: Session ()
waitForKickDone = void $ skipManyTill anyMessage nonTrivialKickDone

Expand All @@ -882,9 +897,11 @@ nonTrivialKickDone = kick (Proxy @"kick/done") >>= guard . not . null
nonTrivialKickStart :: Session ()
nonTrivialKickStart = kick (Proxy @"kick/start") >>= guard . not . null


kick :: KnownSymbol k => Proxy k -> Session [FilePath]
kick proxyMsg = do
NotMess TNotificationMessage{_params} <- customNotification proxyMsg
case fromJSON _params of
Success x -> return x
other -> error $ "Failed to parse kick/done details: " <> show other

Loading

0 comments on commit 507dac7

Please sign in to comment.