diff --git a/.github/workflows/test.yml b/.github/workflows/test.yml index c463b6432f..5b963a662d 100644 --- a/.github/workflows/test.yml +++ b/.github/workflows/test.yml @@ -248,6 +248,10 @@ jobs: name: Test hls-gadt-plugin test suit run: cabal test hls-gadt-plugin --test-options="$TEST_OPTS" || cabal test hls-gadt-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-gadt-plugin --test-options="$TEST_OPTS" + - if: matrix.test + name: Test hls-explicit-fixity-plugin test suite + run: cabal test hls-explicit-fixity-plugin --test-options="$TEST_OPTS" || cabal test hls-explicit-fixity-plugin --test-options="$TEST_OPTS" || LSP_TEST_LOG_COLOR=0 LSP_TEST_LOG_MESSAGES=true LSP_TEST_LOG_STDERR=true cabal test hls-explicit-fixity-plugin --test-options="$TEST_OPTS" + test_post_job: if: always() runs-on: ubuntu-latest diff --git a/cabal.project b/cabal.project index b05eac94f0..9a49ac4fa5 100644 --- a/cabal.project +++ b/cabal.project @@ -30,6 +30,7 @@ packages: ./plugins/hls-change-type-signature-plugin ./plugins/hls-stan-plugin ./plugins/hls-gadt-plugin + ./plugins/hls-explicit-fixity-plugin -- Standard location for temporary packages needed for particular environments -- For example it is used in the project gitlab mirror to help in the MAcOS M1 build script diff --git a/docs/features.md b/docs/features.md index 4b8b10725f..793b66a61e 100644 --- a/docs/features.md +++ b/docs/features.md @@ -50,6 +50,12 @@ Provided by: `ghcide` Type information and documentation on hover, [including from local definitions](./configuration.md#how-to-show-local-documentation-on-hover). +### Show fixity + +Provided by: `hls-explicit-fixity-plugin` + +Provides fixity information. + ## Jump to definition Provided by: `ghcide` diff --git a/exe/Plugins.hs b/exe/Plugins.hs index 561c8541a8..86dbff0a16 100644 --- a/exe/Plugins.hs +++ b/exe/Plugins.hs @@ -91,6 +91,11 @@ import Ide.Plugin.ChangeTypeSignature as ChangeTypeSignature #if hls_gadt import Ide.Plugin.GADT as GADT #endif + +#if explicitFixity +import Ide.Plugin.ExplicitFixity as ExplicitFixity +#endif + -- formatters #if hls_floskell @@ -209,8 +214,14 @@ idePlugins recorder includeExamples = pluginDescToIdePlugins allPlugins -- The ghcide descriptors should come last so that the notification handlers -- (which restart the Shake build) run after everything else GhcIde.descriptors pluginRecorder +#if explicitFixity + -- Make this plugin has a lower priority than ghcide's plugin to ensure + -- type info display first. + ++ [ExplicitFixity.descriptor pluginRecorder] +#endif examplePlugins = [Example.descriptor pluginRecorder "eg" ,Example2.descriptor pluginRecorder "eg2" ,ExampleCabal.descriptor pluginRecorder "ec" ] + diff --git a/ghcide/src/Development/IDE/GHC/Compat/Core.hs b/ghcide/src/Development/IDE/GHC/Compat/Core.hs index 625010fd7c..222be572e6 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Core.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Core.hs @@ -102,6 +102,10 @@ module Development.IDE.GHC.Compat.Core ( #endif -- * Fixity LexicalFixity(..), + Fixity (..), + mi_fix, + defaultFixity, + lookupFixityRn, -- * ModSummary ModSummary(..), -- * HomeModInfo @@ -378,6 +382,7 @@ module Development.IDE.GHC.Compat.Core ( module GHC.Types.Name.Cache, module GHC.Types.Name.Env, module GHC.Types.Name.Reader, + module GHC.Utils.Error, #if MIN_VERSION_ghc(9,2,0) module GHC.Types.Avail, module GHC.Types.SourceFile, @@ -388,7 +393,6 @@ module Development.IDE.GHC.Compat.Core ( module GHC.Types.Unique.Supply, module GHC.Types.Var, module GHC.Unit.Module, - module GHC.Utils.Error, #else module BasicTypes, module Class, @@ -552,6 +556,7 @@ import GHC.Runtime.Context (InteractiveImport (..)) import GHC.Parser.Lexer import qualified GHC.Runtime.Linker as Linker #endif +import GHC.Rename.Fixity (lookupFixityRn) import GHC.Rename.Names import GHC.Rename.Splice import qualified GHC.Runtime.Interpreter as GHCi @@ -568,7 +573,7 @@ import GHC.Tc.Utils.TcType as TcType import qualified GHC.Types.Avail as Avail #if MIN_VERSION_ghc(9,2,0) import GHC.Types.Avail (greNamePrintableName) -import GHC.Types.Fixity (LexicalFixity (..)) +import GHC.Types.Fixity (LexicalFixity (..), Fixity (..), defaultFixity) #endif #if MIN_VERSION_ghc(9,2,0) import GHC.Types.Meta @@ -613,11 +618,11 @@ import GHC.Unit.Module.Imported import GHC.Unit.Module.ModDetails import GHC.Unit.Module.ModGuts import GHC.Unit.Module.ModIface (IfaceExport, ModIface (..), - ModIface_ (..)) + ModIface_ (..), mi_fix) import GHC.Unit.Module.ModSummary (ModSummary (..)) #endif import GHC.Unit.State (ModuleOrigin (..)) -import GHC.Utils.Error (Severity (..)) +import GHC.Utils.Error (Severity (..), emptyMessages) import GHC.Utils.Panic hiding (try) import qualified GHC.Utils.Panic.Plain as Plain #else @@ -688,6 +693,7 @@ import qualified Panic as Plain #endif import Parser import PatSyn +import RnFixity #if MIN_VERSION_ghc(8,8,0) import Plugins #endif diff --git a/haskell-language-server.cabal b/haskell-language-server.cabal index 9dd079bc9a..d786e71530 100644 --- a/haskell-language-server.cabal +++ b/haskell-language-server.cabal @@ -196,6 +196,11 @@ flag gadt default: True manual: True +flag explicitFixity + description: Enable explicitFixity plugin + default: True + manual: True + -- formatters flag floskell @@ -329,6 +334,11 @@ common gadt build-depends: hls-gadt-plugin ^>= 1.0 cpp-options: -Dhls_gadt +common explicitFixity + if flag(explicitFixity) + build-depends: hls-explicit-fixity-plugin ^>= 1.0 + cpp-options: -DexplicitFixity + -- formatters common floskell @@ -382,6 +392,7 @@ executable haskell-language-server , qualifyImportedNames , codeRange , gadt + , explicitFixity , floskell , fourmolu , ormolu diff --git a/plugins/hls-explicit-fixity-plugin/LICENSE b/plugins/hls-explicit-fixity-plugin/LICENSE new file mode 100644 index 0000000000..261eeb9e9f --- /dev/null +++ b/plugins/hls-explicit-fixity-plugin/LICENSE @@ -0,0 +1,201 @@ + Apache License + Version 2.0, January 2004 + http://www.apache.org/licenses/ + + TERMS AND CONDITIONS FOR USE, REPRODUCTION, AND DISTRIBUTION + + 1. Definitions. + + "License" shall mean the terms and conditions for use, reproduction, + and distribution as defined by Sections 1 through 9 of this document. + + "Licensor" shall mean the copyright owner or entity authorized by + the copyright owner that is granting the License. + + "Legal Entity" shall mean the union of the acting entity and all + other entities that control, are controlled by, or are under common + control with that entity. For the purposes of this definition, + "control" means (i) the power, direct or indirect, to cause the + direction or management of such entity, whether by contract or + otherwise, or (ii) ownership of fifty percent (50%) or more of the + outstanding shares, or (iii) beneficial ownership of such entity. + + "You" (or "Your") shall mean an individual or Legal Entity + exercising permissions granted by this License. + + "Source" form shall mean the preferred form for making modifications, + including but not limited to software source code, documentation + source, and configuration files. + + "Object" form shall mean any form resulting from mechanical + transformation or translation of a Source form, including but + not limited to compiled object code, generated documentation, + and conversions to other media types. + + "Work" shall mean the work of authorship, whether in Source or + Object form, made available under the License, as indicated by a + copyright notice that is included in or attached to the work + (an example is provided in the Appendix below). + + "Derivative Works" shall mean any work, whether in Source or Object + form, that is based on (or derived from) the Work and for which the + editorial revisions, annotations, elaborations, or other modifications + represent, as a whole, an original work of authorship. For the purposes + of this License, Derivative Works shall not include works that remain + separable from, or merely link (or bind by name) to the interfaces of, + the Work and Derivative Works thereof. + + "Contribution" shall mean any work of authorship, including + the original version of the Work and any modifications or additions + to that Work or Derivative Works thereof, that is intentionally + submitted to Licensor for inclusion in the Work by the copyright owner + or by an individual or Legal Entity authorized to submit on behalf of + the copyright owner. For the purposes of this definition, "submitted" + means any form of electronic, verbal, or written communication sent + to the Licensor or its representatives, including but not limited to + communication on electronic mailing lists, source code control systems, + and issue tracking systems that are managed by, or on behalf of, the + Licensor for the purpose of discussing and improving the Work, but + excluding communication that is conspicuously marked or otherwise + designated in writing by the copyright owner as "Not a Contribution." + + "Contributor" shall mean Licensor and any individual or Legal Entity + on behalf of whom a Contribution has been received by Licensor and + subsequently incorporated within the Work. + + 2. Grant of Copyright License. Subject to the terms and conditions of + this License, each Contributor hereby grants to You a perpetual, + worldwide, non-exclusive, no-charge, royalty-free, irrevocable + copyright license to reproduce, prepare Derivative Works of, + publicly display, publicly perform, sublicense, and distribute the + Work and such Derivative Works in Source or Object form. + + 3. Grant of Patent License. Subject to the terms and conditions of + this License, each Contributor hereby grants to You a perpetual, + worldwide, non-exclusive, no-charge, royalty-free, irrevocable + (except as stated in this section) patent license to make, have made, + use, offer to sell, sell, import, and otherwise transfer the Work, + where such license applies only to those patent claims licensable + by such Contributor that are necessarily infringed by their + Contribution(s) alone or by combination of their Contribution(s) + with the Work to which such Contribution(s) was submitted. If You + institute patent litigation against any entity (including a + cross-claim or counterclaim in a lawsuit) alleging that the Work + or a Contribution incorporated within the Work constitutes direct + or contributory patent infringement, then any patent licenses + granted to You under this License for that Work shall terminate + as of the date such litigation is filed. + + 4. Redistribution. You may reproduce and distribute copies of the + Work or Derivative Works thereof in any medium, with or without + modifications, and in Source or Object form, provided that You + meet the following conditions: + + (a) You must give any other recipients of the Work or + Derivative Works a copy of this License; and + + (b) You must cause any modified files to carry prominent notices + stating that You changed the files; and + + (c) You must retain, in the Source form of any Derivative Works + that You distribute, all copyright, patent, trademark, and + attribution notices from the Source form of the Work, + excluding those notices that do not pertain to any part of + the Derivative Works; and + + (d) If the Work includes a "NOTICE" text file as part of its + distribution, then any Derivative Works that You distribute must + include a readable copy of the attribution notices contained + within such NOTICE file, excluding those notices that do not + pertain to any part of the Derivative Works, in at least one + of the following places: within a NOTICE text file distributed + as part of the Derivative Works; within the Source form or + documentation, if provided along with the Derivative Works; or, + within a display generated by the Derivative Works, if and + wherever such third-party notices normally appear. The contents + of the NOTICE file are for informational purposes only and + do not modify the License. You may add Your own attribution + notices within Derivative Works that You distribute, alongside + or as an addendum to the NOTICE text from the Work, provided + that such additional attribution notices cannot be construed + as modifying the License. + + You may add Your own copyright statement to Your modifications and + may provide additional or different license terms and conditions + for use, reproduction, or distribution of Your modifications, or + for any such Derivative Works as a whole, provided Your use, + reproduction, and distribution of the Work otherwise complies with + the conditions stated in this License. + + 5. Submission of Contributions. Unless You explicitly state otherwise, + any Contribution intentionally submitted for inclusion in the Work + by You to the Licensor shall be under the terms and conditions of + this License, without any additional terms or conditions. + Notwithstanding the above, nothing herein shall supersede or modify + the terms of any separate license agreement you may have executed + with Licensor regarding such Contributions. + + 6. Trademarks. This License does not grant permission to use the trade + names, trademarks, service marks, or product names of the Licensor, + except as required for reasonable and customary use in describing the + origin of the Work and reproducing the content of the NOTICE file. + + 7. Disclaimer of Warranty. Unless required by applicable law or + agreed to in writing, Licensor provides the Work (and each + Contributor provides its Contributions) on an "AS IS" BASIS, + WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or + implied, including, without limitation, any warranties or conditions + of TITLE, NON-INFRINGEMENT, MERCHANTABILITY, or FITNESS FOR A + PARTICULAR PURPOSE. You are solely responsible for determining the + appropriateness of using or redistributing the Work and assume any + risks associated with Your exercise of permissions under this License. + + 8. Limitation of Liability. In no event and under no legal theory, + whether in tort (including negligence), contract, or otherwise, + unless required by applicable law (such as deliberate and grossly + negligent acts) or agreed to in writing, shall any Contributor be + liable to You for damages, including any direct, indirect, special, + incidental, or consequential damages of any character arising as a + result of this License or out of the use or inability to use the + Work (including but not limited to damages for loss of goodwill, + work stoppage, computer failure or malfunction, or any and all + other commercial damages or losses), even if such Contributor + has been advised of the possibility of such damages. + + 9. Accepting Warranty or Additional Liability. While redistributing + the Work or Derivative Works thereof, You may choose to offer, + and charge a fee for, acceptance of support, warranty, indemnity, + or other liability obligations and/or rights consistent with this + License. However, in accepting such obligations, You may act only + on Your own behalf and on Your sole responsibility, not on behalf + of any other Contributor, and only if You agree to indemnify, + defend, and hold each Contributor harmless for any liability + incurred by, or claims asserted against, such Contributor by reason + of your accepting any such warranty or additional liability. + + END OF TERMS AND CONDITIONS + + APPENDIX: How to apply the Apache License to your work. + + To apply the Apache License to your work, attach the following + boilerplate notice, with the fields enclosed by brackets "[]" + replaced with your own identifying information. (Don't include + the brackets!) The text should be enclosed in the appropriate + comment syntax for the file format. We also recommend that a + file or class name and description of purpose be included on the + same "printed page" as the copyright notice for easier + identification within third-party archives. + + Copyright [yyyy] [name of copyright owner] + + Licensed under the Apache License, Version 2.0 (the "License"); + you may not use this file except in compliance with the License. + You may obtain a copy of the License at + + http://www.apache.org/licenses/LICENSE-2.0 + + Unless required by applicable law or agreed to in writing, software + distributed under the License is distributed on an "AS IS" BASIS, + WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. + See the License for the specific language governing permissions and + limitations under the License. diff --git a/plugins/hls-explicit-fixity-plugin/README.md b/plugins/hls-explicit-fixity-plugin/README.md new file mode 100644 index 0000000000..409ff7f3dc --- /dev/null +++ b/plugins/hls-explicit-fixity-plugin/README.md @@ -0,0 +1,13 @@ +# Explicit Fixity Plugin + +The hls-explicit-fixity-plugin will show available fixity explicitly while hovering. + +## Demo + +![fixity1](./fixity1.png) + +![fixity2](./fixity2.png) + +## Change log +### 1.0.0.0 +- Released! diff --git a/plugins/hls-explicit-fixity-plugin/fixity1.png b/plugins/hls-explicit-fixity-plugin/fixity1.png new file mode 100644 index 0000000000..0f88fd53d5 Binary files /dev/null and b/plugins/hls-explicit-fixity-plugin/fixity1.png differ diff --git a/plugins/hls-explicit-fixity-plugin/fixity2.png b/plugins/hls-explicit-fixity-plugin/fixity2.png new file mode 100644 index 0000000000..7798192a39 Binary files /dev/null and b/plugins/hls-explicit-fixity-plugin/fixity2.png differ diff --git a/plugins/hls-explicit-fixity-plugin/hls-explicit-fixity-plugin.cabal b/plugins/hls-explicit-fixity-plugin/hls-explicit-fixity-plugin.cabal new file mode 100644 index 0000000000..087c1466b6 --- /dev/null +++ b/plugins/hls-explicit-fixity-plugin/hls-explicit-fixity-plugin.cabal @@ -0,0 +1,52 @@ +cabal-version: 2.4 +name: hls-explicit-fixity-plugin +version: 1.0.0.0 +synopsis: Show fixity explicitly while hovering +description: + Please see the README on GitHub at + +license: Apache-2.0 +license-file: LICENSE +author: Lei Zhu +maintainer: julytreee@gmail.com +category: Development +build-type: Simple +extra-source-files: + LICENSE + test/testdata/*.hs + +library + exposed-modules: Ide.Plugin.ExplicitFixity + + hs-source-dirs: src + build-depends: + base >=4.12 && <5 + , containers + , deepseq + , extra + , ghc + , ghcide ^>=1.7 + , hashable + , hls-plugin-api ^>=1.4 + , lsp >=1.2.0.1 + , text + + ghc-options: + -Wall + -Wno-name-shadowing + -Wno-unticked-promoted-constructors + default-language: Haskell2010 + default-extensions: DataKinds + +test-suite tests + type: exitcode-stdio-1.0 + default-language: Haskell2010 + hs-source-dirs: test + main-is: Main.hs + ghc-options: -threaded -rtsopts -with-rtsopts=-N + build-depends: + , base + , filepath + , hls-explicit-fixity-plugin + , hls-test-utils ^>=1.3 + , text diff --git a/plugins/hls-explicit-fixity-plugin/src/Ide/Plugin/ExplicitFixity.hs b/plugins/hls-explicit-fixity-plugin/src/Ide/Plugin/ExplicitFixity.hs new file mode 100644 index 0000000000..fb4e1c1d06 --- /dev/null +++ b/plugins/hls-explicit-fixity-plugin/src/Ide/Plugin/ExplicitFixity.hs @@ -0,0 +1,165 @@ +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE TypeFamilies #-} +{-# OPTIONS_GHC -Wno-deprecations #-} +{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-} +{-# HLINT ignore "Use nubOrdOn" #-} + +module Ide.Plugin.ExplicitFixity(descriptor) where + +import Control.DeepSeq +import Control.Monad (forM) +import Control.Monad.IO.Class (MonadIO, liftIO) +import Data.Coerce (coerce) +import Data.Either.Extra +import Data.Hashable +import Data.List.Extra (nubOn) +import qualified Data.Map as M +import Data.Maybe +import Data.Monoid +import qualified Data.Text as T +import Development.IDE hiding (pluginHandlers, + pluginRules) +import Development.IDE.Core.PositionMapping (idDelta) +import Development.IDE.Core.Shake (addPersistentRule) +import qualified Development.IDE.Core.Shake as Shake +import Development.IDE.GHC.Compat +import Development.IDE.GHC.Compat.Util (FastString) +import qualified Development.IDE.GHC.Compat.Util as Util +import GHC.Generics (Generic) +import Ide.PluginUtils (getNormalizedFilePath, + handleMaybeM, + pluginResponse) +import Ide.Types hiding (pluginId) +import Language.LSP.Types + +pluginId :: PluginId +pluginId = "explicitFixity" + +descriptor :: Recorder (WithPriority Log) -> PluginDescriptor IdeState +descriptor recorder = (defaultPluginDescriptor pluginId) + { pluginRules = fixityRule recorder + , pluginHandlers = mkPluginHandler STextDocumentHover hover + } + +hover :: PluginMethodHandler IdeState TextDocumentHover +hover state plId (HoverParams (TextDocumentIdentifier uri) pos _) = pluginResponse $ do + nfp <- getNormalizedFilePath plId uri + fixityTrees <- handleMaybeM "ExplicitFixity: Unable to get fixity" + $ liftIO + $ runAction "ExplicitFixity.GetFixity" state + $ use GetFixity nfp + -- We don't have much fixities on one position, so `nubOn` is acceptable. + pure $ toHover $ nubOn snd $ findInTree fixityTrees pos fNodeFixty + where + toHover :: [(T.Text, Fixity)] -> Maybe Hover + toHover [] = Nothing + toHover fixities = + let -- Splicing fixity info + contents = T.intercalate "\n\n" $ fixityText <$> fixities + -- Append to the previous hover content + contents' = "\n" <> sectionSeparator <> contents + in Just $ Hover (HoverContents $ unmarkedUpContent contents') Nothing + + fixityText :: (T.Text, Fixity) -> T.Text + fixityText (name, Fixity _ precedence direction) = + printOutputable direction <> " " <> printOutputable precedence <> " `" <> name <> "`" + +-- | Transferred from ghc `selectSmallestContaining` +selectSmallestContainingForFixityTree :: Span -> FixityTree -> Maybe FixityTree +selectSmallestContainingForFixityTree sp node + | sp `containsSpan` fNodeSpan node = Just node + | fNodeSpan node `containsSpan` sp = getFirst $ mconcat + [ foldMap (First . selectSmallestContainingForFixityTree sp) $ fNodeChildren node + , First (Just node) + ] + | otherwise = Nothing + +-- | Transferred from ghcide `pointCommand` +findInTree :: FixityTrees -> Position -> (FixityTree -> [a]) -> [a] +findInTree tree pos k = + concat $ M.elems $ flip M.mapWithKey tree $ \fs ast -> + maybe [] k (selectSmallestContainingForFixityTree (sp fs) ast) + where + sloc fs = mkRealSrcLoc fs (fromIntegral $ line+1) (fromIntegral $ cha+1) + sp fs = mkRealSrcSpan (sloc fs) (sloc fs) + line = _line pos + cha = _character pos + +data FixityTree = FNode + { fNodeSpan :: Span + , fNodeChildren :: [FixityTree] + , fNodeFixty :: [(T.Text, Fixity)] + } deriving (Generic) + +instance NFData FixityTree where + rnf = rwhnf + +instance Show FixityTree where + show _ = "" + +type FixityTrees = M.Map FastString FixityTree + +newtype Log = LogShake Shake.Log + +instance Pretty Log where + pretty = \case + LogShake log -> pretty log + +data GetFixity = GetFixity deriving (Show, Eq, Generic) + +instance Hashable GetFixity +instance NFData GetFixity + +type instance RuleResult GetFixity = FixityTrees + +fakeFixityTrees :: FixityTrees +fakeFixityTrees = M.empty + +-- | Convert a HieASTs to FixityTrees with fixity info gathered +hieAstsToFixitTrees :: MonadIO m => HscEnv -> TcGblEnv -> HieASTs a -> m FixityTrees +hieAstsToFixitTrees hscEnv tcGblEnv ast = + -- coerce to avoid compatibility issues. + M.mapKeysWith const coerce <$> + sequence (M.map (hieAstToFixtyTree hscEnv tcGblEnv) (getAsts ast)) + +-- | Convert a HieAST to FixityTree with fixity info gathered +hieAstToFixtyTree :: MonadIO m => HscEnv -> TcGblEnv -> HieAST a -> m FixityTree +hieAstToFixtyTree hscEnv tcGblEnv ast = case ast of + (Node _ span []) -> FNode span [] <$> getFixities + (Node _ span children) -> do + fixities <- getFixities + childrenFixities <- mapM (hieAstToFixtyTree hscEnv tcGblEnv) children + pure $ FNode span childrenFixities fixities + where + -- Names at the current ast node + names :: [Name] + names = mapMaybe eitherToMaybe $ M.keys $ getNodeIds ast + + getFixities :: MonadIO m => m [(T.Text, Fixity)] + getFixities = liftIO + $ fmap (filter ((/= defaultFixity) . snd) . mapMaybe pickFixity) + $ forM names $ \name -> + (,) (printOutputable name) + . snd + <$> Util.handleGhcException + (const $ pure (emptyMessages, Nothing)) + (initTcWithGbl hscEnv tcGblEnv (realSrcLocSpan $ mkRealSrcLoc "" 1 1) (lookupFixityRn name)) + + pickFixity :: (T.Text, Maybe Fixity) -> Maybe (T.Text, Fixity) + pickFixity (_, Nothing) = Nothing + pickFixity (name, Just f) = Just (name, f) + +fixityRule :: Recorder (WithPriority Log) -> Rules () +fixityRule recorder = do + define (cmapWithPrio LogShake recorder) $ \GetFixity nfp -> do + HAR{hieAst} <- use_ GetHieAst nfp + env <- hscEnv <$> use_ GhcSession nfp + tcGblEnv <- tmrTypechecked <$> use_ TypeCheck nfp + trees <- hieAstsToFixitTrees env tcGblEnv hieAst + pure ([], Just trees) + + -- Ensure that this plugin doesn't block on startup + addPersistentRule GetFixity $ \_ -> pure $ Just (fakeFixityTrees, idDelta, Nothing) diff --git a/plugins/hls-explicit-fixity-plugin/test/Main.hs b/plugins/hls-explicit-fixity-plugin/test/Main.hs new file mode 100644 index 0000000000..52367e215c --- /dev/null +++ b/plugins/hls-explicit-fixity-plugin/test/Main.hs @@ -0,0 +1,70 @@ +{-# LANGUAGE OverloadedStrings #-} + +module Main where + +import qualified Data.Text as T +import Ide.Plugin.ExplicitFixity (descriptor) +import System.FilePath +import Test.Hls + +plugin :: PluginDescriptor IdeState +plugin = descriptor mempty + +main :: IO () +main = defaultTestRunner tests + +tests :: TestTree +tests = testGroup "Explicit fixity" + [ hoverTest "(++)" (Position 5 7) "infixr 5 `++`" + , hoverTest "($)" (Position 6 7) "infixr 0 `$`" + , hoverTest "(.)" (Position 7 7) "infixr 9 `.`" + , hoverTest "(+)" (Position 8 7) "infixl 6 `+`" + , hoverTest "(-)" (Position 9 8) "infixl 6 `-`" + , hoverTest "(<>)" (Position 10 7) "infixr 6 `<>`" + , hoverTest "(>>=)" (Position 11 7) "infixl 1 `>>=`" + , hoverTest "(>=>)" (Position 12 7) "infixr 1 `>=>`" + , hoverTest "elem" (Position 13 7) "infix 4 `elem`" + , hoverTest "on" (Position 14 7) "infixl 0 `on`" + , hoverTest "(||)" (Position 15 8) "infixr 2 `||`" + , hoverTest "mod" (Position 16 8) "infixl 7 `mod`" + , hoverTest "(**)" (Position 17 8) "infixr 8 `**`" + , hoverTest "(^)" (Position 18 8) "infixr 8 `^`" + , hoverTest "(<$)" (Position 19 8) "infixl 4 `<$`" + , hoverTest "seq" (Position 20 9) "infixr 0 `seq`" + , hoverTest "(<|>)" (Position 21 8) "infixl 3 `<|>`" + , hoverTest "fixity define" (Position 23 11) "infixr 7 `>>:`" + , hoverTest "record" (Position 28 10) "infix 9 `>>::`" + , hoverTest "wildcards" (Position 30 5) "infixr 7 `>>:` \n \ninfix 9 `>>::`" + , hoverTest "function" (Position 32 11) "infixl 1 `f`" + , hoverTest "signature" (Position 35 2) "infixr 9 `>>>:`" + , hoverTest "operator" (Position 36 2) "infixr 9 `>>>:`" + , hoverTest "escape" (Position 39 2) "infixl 3 `~\\:`" + -- Ensure that there is no one extra new line in import statement + , expectFail $ hoverTest "import" (Position 2 18) "Control.Monad***" + -- Known issue, See https://github.com/haskell/haskell-language-server/pull/2973/files#r916535742 + , expectFail $ hoverTestImport "import" (Position 4 7) "infixr 9 `>>>:`" + ] + +hoverTest :: TestName -> Position -> T.Text -> TestTree +hoverTest = hoverTest' "Hover.hs" +hoverTestImport :: TestName -> Position -> T.Text -> TestTree +hoverTestImport = hoverTest' "HoverImport.hs" + +hoverTest' :: String -> TestName -> Position -> T.Text -> TestTree +hoverTest' docName title pos expected = testCase title $ runSessionWithServer plugin testDataDir $ do + doc <- openDoc docName "haskell" + waitForKickDone + h <- getHover doc pos + let expected' = "\n" <> sectionSeparator <> expected + case h of + Nothing -> liftIO $ assertFailure "No hover" + Just (Hover contents _) -> case contents of + HoverContentsMS _ -> liftIO $ assertFailure "Unexpected content type" + HoverContents (MarkupContent mk txt) -> do + liftIO + $ assertBool ("Failed to find `" <> T.unpack expected <> "` in hover message: " <> T.unpack txt) + $ expected `T.isInfixOf` txt + closeDoc doc + +testDataDir :: FilePath +testDataDir = "test" "testdata" diff --git a/plugins/hls-explicit-fixity-plugin/test/testdata/Hover.hs b/plugins/hls-explicit-fixity-plugin/test/testdata/Hover.hs new file mode 100644 index 0000000000..f5fd50a501 --- /dev/null +++ b/plugins/hls-explicit-fixity-plugin/test/testdata/Hover.hs @@ -0,0 +1,40 @@ +{-# LANGUAGE RecordWildCards #-} +module Hover where +import Control.Monad +import Data.Function (on) +import Control.Applicative ((<|>)) +f1 = (++) +f2 = ($) +f3 = (.) +f4 = (+) +f5 = 1 - 2 +f6 = (<>) +f7 = (>>=) +f8 = (>=>) +f9 = elem +f10 = on +f11 = (||) +f12 = mod +f13 = (**) +f14 = (^) +f15 = (<$) +f16 = seq +f17 = (<|>) + +infixr 7 >>: +infix 9 >>:: +data F = G + { (>>:) :: Int -> Int -> Int + , c :: Int + , (>>::) :: Char + } +f G{..} = undefined + +infixl 1 `f` + +infixr 9 >>>: +(>>>:) :: Int -> Int +(>>>:) x = 3 + +infixl 3 ~\: +(~\:) x y = 3 diff --git a/plugins/hls-explicit-fixity-plugin/test/testdata/HoverImport.hs b/plugins/hls-explicit-fixity-plugin/test/testdata/HoverImport.hs new file mode 100644 index 0000000000..e3474eb0c3 --- /dev/null +++ b/plugins/hls-explicit-fixity-plugin/test/testdata/HoverImport.hs @@ -0,0 +1,5 @@ +module HoverImport where + +import Hover + +g = (>>>:) diff --git a/plugins/hls-explicit-fixity-plugin/test/testdata/hie.yaml b/plugins/hls-explicit-fixity-plugin/test/testdata/hie.yaml new file mode 100644 index 0000000000..824558147d --- /dev/null +++ b/plugins/hls-explicit-fixity-plugin/test/testdata/hie.yaml @@ -0,0 +1,3 @@ +cradle: + direct: + arguments: [] diff --git a/stack-lts16.yaml b/stack-lts16.yaml index 826f8730e4..32a1e3f5ba 100644 --- a/stack-lts16.yaml +++ b/stack-lts16.yaml @@ -32,6 +32,7 @@ packages: - ./plugins/hls-code-range-plugin - ./plugins/hls-change-type-signature-plugin - ./plugins/hls-gadt-plugin + - ./plugins/hls-explicit-fixity-plugin ghc-options: "$everything": -haddock diff --git a/stack-lts19.yaml b/stack-lts19.yaml index 6beff15f8b..53c00671e8 100644 --- a/stack-lts19.yaml +++ b/stack-lts19.yaml @@ -31,6 +31,7 @@ packages: - ./plugins/hls-code-range-plugin - ./plugins/hls-change-type-signature-plugin - ./plugins/hls-gadt-plugin + - ./plugins/hls-explicit-fixity-plugin ghc-options: "$everything": -haddock diff --git a/stack.yaml b/stack.yaml index 31af6039e1..72e06a135d 100644 --- a/stack.yaml +++ b/stack.yaml @@ -31,6 +31,7 @@ packages: - ./plugins/hls-code-range-plugin - ./plugins/hls-change-type-signature-plugin - ./plugins/hls-gadt-plugin +- ./plugins/hls-explicit-fixity-plugin extra-deps: - floskell-0.10.6@sha256:e77d194189e8540abe2ace2c7cb8efafc747ca35881a2fefcbd2d40a1292e036,3819