Skip to content

Commit

Permalink
Use exact print for suggest missing constraint code actions (#1221)
Browse files Browse the repository at this point in the history
* Cache annotated AST

* instance ASTElement RdrName

* appendConstraint + Rewrite abstraction

The Rewrite abstraction is similar to D.IDE.GHC.ExactPrint.Graft but it
does fewer things more efficiently:

- It doesn't annotate things for you (so it doesn't destroy user format)
- It doesn't provide a Monoid instance (for now)
- It doesn't need a fully parsed source
- It doesn't use SYB to perform the replacement
- It doesn't diff to compute the result

The use case is code actions where you don't have the SrcSpan that you need to
edit at hand, and instead you need to traverse the AST manually to locate the declaration to edit

* Refactor suggest constraint code action to use exactprint

Tweaking the suggest constraints tests to reflect the increased precision in
whitespace preservation

* Catch missing 'Monad m' constraints too

* Suggestions for missing implicit parameters

* hlints

* compat

* Include getAnnotatedParsedSourceRule in the main rule

Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
  • Loading branch information
pepeiborra and mergify[bot] committed Jan 17, 2021
1 parent 6f105bd commit 0403dbf
Show file tree
Hide file tree
Showing 7 changed files with 417 additions and 140 deletions.
1 change: 1 addition & 0 deletions ghcide/ghcide.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -169,6 +169,7 @@ library
Development.IDE.Plugin
Development.IDE.Plugin.Completions
Development.IDE.Plugin.CodeAction
Development.IDE.Plugin.CodeAction.ExactPrint
Development.IDE.Plugin.HLS
Development.IDE.Plugin.HLS.GhcIde
Development.IDE.Plugin.Test
Expand Down
2 changes: 2 additions & 0 deletions ghcide/src/Development/IDE/Core/Rules.hs
Original file line number Diff line number Diff line change
Expand Up @@ -79,6 +79,7 @@ import Development.IDE.Core.FileStore (modificationTime, getFil
import Development.IDE.Types.Diagnostics as Diag
import Development.IDE.Types.Location
import Development.IDE.GHC.Compat hiding (parseModule, typecheckModule, writeHieFile, TargetModule, TargetFile)
import Development.IDE.GHC.ExactPrint
import Development.IDE.GHC.Util
import Data.Either.Extra
import qualified Development.IDE.Types.Logger as L
Expand Down Expand Up @@ -1020,6 +1021,7 @@ mainRule = do
needsCompilationRule
generateCoreRule
getImportMapRule
getAnnotatedParsedSourceRule

-- | Given the path to a module src file, this rule returns True if the
-- corresponding `.hi` file is stable, that is, if it is newer
Expand Down
46 changes: 37 additions & 9 deletions ghcide/src/Development/IDE/GHC/ExactPrint.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,21 +3,29 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}

module Development.IDE.GHC.ExactPrint
( Graft(..),
graft,
graftDecls,
graftDeclsWithM,
annotate,
hoistGraft,
graftWithM,
graftWithSmallestM,
transform,
transformM,
useAnnotatedSource,
annotateParsedSource,
getAnnotatedParsedSourceRule,
GetAnnotatedParsedSource(..),
ASTElement (..),
ExceptStringT (..),
Annotated(..),
TransformT,
Anns,
Annotate,
)
where

Expand All @@ -35,10 +43,13 @@ import Data.Functor.Classes
import Data.Functor.Contravariant
import qualified Data.Text as T
import Development.IDE.Core.RuleTypes
import Development.IDE.Core.Rules
import Development.IDE.Core.Service (runAction)
import Development.IDE.Core.Shake
import Development.IDE.GHC.Compat hiding (parseExpr)
import Development.IDE.Types.Location
import Development.Shake (RuleResult, Rules)
import Development.Shake.Classes
import qualified GHC.Generics as GHC
import Generics.SYB
import Ide.PluginUtils
import Language.Haskell.GHC.ExactPrint
Expand All @@ -47,26 +58,38 @@ import Language.Haskell.LSP.Types
import Language.Haskell.LSP.Types.Capabilities (ClientCapabilities)
import Outputable (Outputable, ppr, showSDoc)
import Retrie.ExactPrint hiding (parseDecl, parseExpr, parsePattern, parseType)
import Parser (parseIdentifier)
#if __GLASGOW_HASKELL__ == 808
import Control.Arrow
#endif


------------------------------------------------------------------------------

data GetAnnotatedParsedSource = GetAnnotatedParsedSource
deriving (Eq, Show, Typeable, GHC.Generic)

instance Hashable GetAnnotatedParsedSource
instance NFData GetAnnotatedParsedSource
instance Binary GetAnnotatedParsedSource
type instance RuleResult GetAnnotatedParsedSource = Annotated ParsedSource

-- | Get the latest version of the annotated parse source.
useAnnotatedSource ::
String ->
IdeState ->
NormalizedFilePath ->
IO (Maybe (Annotated ParsedSource))
useAnnotatedSource herald state nfp =
fmap annotateParsedSource
<$> runAction herald state (use GetParsedModule nfp)
getAnnotatedParsedSourceRule :: Rules ()
getAnnotatedParsedSourceRule = define $ \GetAnnotatedParsedSource nfp -> do
pm <- use GetParsedModule nfp
return ([], fmap annotateParsedSource pm)

annotateParsedSource :: ParsedModule -> Annotated ParsedSource
annotateParsedSource = fixAnns

useAnnotatedSource ::
String ->
IdeState ->
NormalizedFilePath ->
IO (Maybe (Annotated ParsedSource))
useAnnotatedSource herald state nfp =
runAction herald state (use GetAnnotatedParsedSource nfp)
------------------------------------------------------------------------------

{- | A transformation for grafting source trees together. Use the semigroup
Expand Down Expand Up @@ -291,6 +314,10 @@ instance p ~ GhcPs => ASTElement (HsDecl p) where
parseAST = parseDecl
maybeParensAST = id

instance ASTElement RdrName where
parseAST df fp = parseWith df fp parseIdentifier
maybeParensAST = id

------------------------------------------------------------------------------

-- | Dark magic I stole from retrie. No idea what it does.
Expand All @@ -302,6 +329,7 @@ fixAnns ParsedModule {..} =
------------------------------------------------------------------------------

-- | Given an 'LHSExpr', compute its exactprint annotations.
-- Note that this function will throw away any existing annotations (and format)
annotate :: ASTElement ast => DynFlags -> Located ast -> TransformT (Either String) (Anns, Located ast)
annotate dflags ast = do
uniq <- show <$> uniqueSrcSpanT
Expand Down
7 changes: 7 additions & 0 deletions ghcide/src/Development/IDE/GHC/Orphans.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,7 @@ import GhcPlugins
import qualified StringBuffer as SB
import Data.Text (Text)
import Data.String (IsString(fromString))
import Retrie.ExactPrint (Annotated)


-- Orphan instances for types from the GHC API.
Expand Down Expand Up @@ -144,3 +145,9 @@ instance NFData ModGuts where

instance NFData (ImportDecl GhcPs) where
rnf = rwhnf

instance Show (Annotated ParsedSource) where
show _ = "<Annotated ParsedSource>"

instance NFData (Annotated ParsedSource) where
rnf = rwhnf
Loading

0 comments on commit 0403dbf

Please sign in to comment.