diff --git a/ghcide/src/Development/IDE/Plugin/CodeAction.hs b/ghcide/src/Development/IDE/Plugin/CodeAction.hs index 41a508335d..43354a11e9 100644 --- a/ghcide/src/Development/IDE/Plugin/CodeAction.hs +++ b/ghcide/src/Development/IDE/Plugin/CodeAction.hs @@ -234,8 +234,8 @@ findDeclContainingLoc loc = find (\(L l _) -> loc `isInsideSrcSpan` l) -- imported from ‘Data.ByteString’ at B.hs:6:1-22 -- imported from ‘Data.ByteString.Lazy’ at B.hs:8:1-27 -- imported from ‘Data.Text’ at B.hs:7:1-16 -suggestHideShadow :: ParsedSource -> Maybe TcModuleResult -> Maybe HieAstResult -> Diagnostic -> [(T.Text, [Either TextEdit Rewrite])] -suggestHideShadow ps@(L _ HsModule {hsmodImports}) mTcM mHar Diagnostic {_message, _range} +suggestHideShadow :: ParsedSource -> T.Text -> Maybe TcModuleResult -> Maybe HieAstResult -> Diagnostic -> [(T.Text, [Either TextEdit Rewrite])] +suggestHideShadow ps@(L _ HsModule {hsmodImports}) fileContents mTcM mHar Diagnostic {_message, _range} | Just [identifier, modName, s] <- matchRegexUnifySpaces _message @@ -260,7 +260,7 @@ suggestHideShadow ps@(L _ HsModule {hsmodImports}) mTcM mHar Diagnostic {_messag mDecl <- findImportDeclByModuleName hsmodImports $ T.unpack modName, title <- "Hide " <> identifier <> " from " <> modName = if modName == "Prelude" && null mDecl - then maybeToList $ (\(_, te) -> (title, [Left te])) <$> newImportToEdit (hideImplicitPreludeSymbol identifier) ps + then maybeToList $ (\(_, te) -> (title, [Left te])) <$> newImportToEdit (hideImplicitPreludeSymbol identifier) ps fileContents else maybeToList $ (title,) . pure . pure . hideSymbol (T.unpack identifier) <$> mDecl | otherwise = [] @@ -887,9 +887,10 @@ suggestImportDisambiguation :: DynFlags -> Maybe T.Text -> ParsedSource -> + T.Text -> Diagnostic -> [(T.Text, [Either TextEdit Rewrite])] -suggestImportDisambiguation df (Just txt) ps@(L _ HsModule {hsmodImports}) diag@Diagnostic {..} +suggestImportDisambiguation df (Just txt) ps@(L _ HsModule {hsmodImports}) fileContents diag@Diagnostic {..} | Just [ambiguous] <- matchRegexUnifySpaces _message @@ -930,7 +931,7 @@ suggestImportDisambiguation df (Just txt) ps@(L _ HsModule {hsmodImports}) diag@ suggestionsImpl symbol targetsWithRestImports = sortOn fst [ ( renderUniquify mode modNameText symbol - , disambiguateSymbol ps diag symbol mode + , disambiguateSymbol ps fileContents diag symbol mode ) | (modTarget, restImports) <- targetsWithRestImports , let modName = targetModuleName modTarget @@ -964,7 +965,7 @@ suggestImportDisambiguation df (Just txt) ps@(L _ HsModule {hsmodImports}) diag@ <> T.pack (moduleNameString qual) <> "." <> symbol -suggestImportDisambiguation _ _ _ _ = [] +suggestImportDisambiguation _ _ _ _ _ = [] occursUnqualified :: T.Text -> ImportDecl GhcPs -> Bool occursUnqualified symbol ImportDecl{..} @@ -989,11 +990,12 @@ targetModuleName (ExistingImp _) = disambiguateSymbol :: ParsedSource -> + T.Text -> Diagnostic -> T.Text -> HidingMode -> [Either TextEdit Rewrite] -disambiguateSymbol pm Diagnostic {..} (T.unpack -> symbol) = \case +disambiguateSymbol pm fileContents Diagnostic {..} (T.unpack -> symbol) = \case (HideOthers hiddens0) -> [ Right $ hideSymbol symbol idecl | ExistingImp idecls <- hiddens0 @@ -1001,7 +1003,7 @@ disambiguateSymbol pm Diagnostic {..} (T.unpack -> symbol) = \case ] ++ mconcat [ if null imps - then maybeToList $ Left . snd <$> newImportToEdit (hideImplicitPreludeSymbol $ T.pack symbol) pm + then maybeToList $ Left . snd <$> newImportToEdit (hideImplicitPreludeSymbol $ T.pack symbol) pm fileContents else Right . hideSymbol symbol <$> imps | ImplicitPrelude imps <- hiddens0 ] @@ -1203,8 +1205,8 @@ removeRedundantConstraints df (L _ HsModule {hsmodDecls}) Diagnostic{..} ------------------------------------------------------------------------------------------------- -suggestNewOrExtendImportForClassMethod :: ExportsMap -> ParsedSource -> Diagnostic -> [(T.Text, CodeActionKind, [Either TextEdit Rewrite])] -suggestNewOrExtendImportForClassMethod packageExportsMap ps Diagnostic {_message} +suggestNewOrExtendImportForClassMethod :: ExportsMap -> ParsedSource -> T.Text -> Diagnostic -> [(T.Text, CodeActionKind, [Either TextEdit Rewrite])] +suggestNewOrExtendImportForClassMethod packageExportsMap ps fileContents Diagnostic {_message} | Just [methodName, className] <- matchRegexUnifySpaces _message @@ -1229,7 +1231,7 @@ suggestNewOrExtendImportForClassMethod packageExportsMap ps Diagnostic {_message ] -- new _ - | Just (range, indent) <- newImportInsertRange ps + | Just (range, indent) <- newImportInsertRange ps fileContents -> (\(kind, unNewImport -> x) -> (x, kind, [Left $ TextEdit range (x <> "\n" <> T.replicate indent " ")])) <$> [ (quickFixImportKind' "new" style, newUnqualImport moduleNameText rendered False) @@ -1239,8 +1241,8 @@ suggestNewOrExtendImportForClassMethod packageExportsMap ps Diagnostic {_message <> [(quickFixImportKind "new.all", newImportAll moduleNameText)] | otherwise -> [] -suggestNewImport :: ExportsMap -> ParsedSource -> Diagnostic -> [(T.Text, CodeActionKind, TextEdit)] -suggestNewImport packageExportsMap ps@(L _ HsModule {..}) Diagnostic{_message} +suggestNewImport :: ExportsMap -> ParsedSource -> T.Text -> Diagnostic -> [(T.Text, CodeActionKind, TextEdit)] +suggestNewImport packageExportsMap ps@(L _ HsModule {..}) fileContents Diagnostic{_message} | msg <- unifySpaces _message , Just thingMissing <- extractNotInScopeName msg , qual <- extractQualifiedModuleName msg @@ -1249,13 +1251,13 @@ suggestNewImport packageExportsMap ps@(L _ HsModule {..}) Diagnostic{_message} >>= (findImportDeclByModuleName hsmodImports . T.unpack) >>= ideclAs . unLoc <&> T.pack . moduleNameString . unLoc - , Just (range, indent) <- newImportInsertRange ps + , Just (range, indent) <- newImportInsertRange ps fileContents , extendImportSuggestions <- matchRegexUnifySpaces msg "Perhaps you want to add ‘[^’]*’ to the import list in the import of ‘([^’]*)’" = sortOn fst3 [(imp, kind, TextEdit range (imp <> "\n" <> T.replicate indent " ")) | (kind, unNewImport -> imp) <- constructNewImportSuggestions packageExportsMap (qual <|> qual', thingMissing) extendImportSuggestions ] -suggestNewImport _ _ _ = [] +suggestNewImport _ _ _ _ = [] constructNewImportSuggestions :: ExportsMap -> (Maybe T.Text, NotInScope) -> Maybe [T.Text] -> [(CodeActionKind, NewImport)] @@ -1282,26 +1284,70 @@ constructNewImportSuggestions exportsMap (qual, thingMissing) notTheseModules = newtype NewImport = NewImport {unNewImport :: T.Text} deriving (Show, Eq, Ord) -newImportToEdit :: NewImport -> ParsedSource -> Maybe (T.Text, TextEdit) -newImportToEdit (unNewImport -> imp) ps - | Just (range, indent) <- newImportInsertRange ps +newImportToEdit :: NewImport -> ParsedSource -> T.Text -> Maybe (T.Text, TextEdit) +newImportToEdit (unNewImport -> imp) ps fileContents + | Just (range, indent) <- newImportInsertRange ps fileContents = Just (imp, TextEdit range (imp <> "\n" <> T.replicate indent " ")) | otherwise = Nothing -newImportInsertRange :: ParsedSource -> Maybe (Range, Int) -newImportInsertRange (L _ HsModule {..}) +-- | Finds the next valid position for inserting a new import declaration +-- * If the file already has existing imports it will be inserted under the last of these, +-- it is assumed that the existing last import declaration is in a valid position +-- * If the file does not have existing imports, but has a (module ... where) declaration, +-- the new import will be inserted directly under this declaration (accounting for explicit exports) +-- * If the file has neither existing imports nor a module declaration, +-- the import will be inserted at line zero if there are no pragmas, +-- * otherwise inserted one line after the last file-header pragma +newImportInsertRange :: ParsedSource -> T.Text -> Maybe (Range, Int) +newImportInsertRange (L _ HsModule {..}) fileContents | Just (uncurry Position -> insertPos, col) <- case hsmodImports of - [] -> case getLoc (head hsmodDecls) of - OldRealSrcSpan s -> let col = srcLocCol (realSrcSpanStart s) - 1 - in Just ((srcLocLine (realSrcSpanStart s) - 1, col), col) - _ -> Nothing - _ -> case getLoc (last hsmodImports) of - OldRealSrcSpan s -> let col = srcLocCol (realSrcSpanStart s) - 1 - in Just ((srcLocLine $ realSrcSpanEnd s,col), col) - _ -> Nothing + [] -> findPositionNoImports hsmodName hsmodExports fileContents + _ -> findPositionFromImportsOrModuleDecl hsmodImports last True = Just (Range insertPos insertPos, col) | otherwise = Nothing +-- | Insert the import under the Module declaration exports if they exist, otherwise just under the module declaration. +-- If no module declaration exists, then no exports will exist either, in that case +-- insert the import after any file-header pragmas or at position zero if there are no pragmas +findPositionNoImports :: Maybe (Located ModuleName) -> Maybe (Located [LIE name]) -> T.Text -> Maybe ((Int, Int), Int) +findPositionNoImports Nothing _ fileContents = findNextPragmaPosition fileContents +findPositionNoImports _ (Just hsmodExports) _ = findPositionFromImportsOrModuleDecl hsmodExports id False +findPositionNoImports (Just hsmodName) _ _ = findPositionFromImportsOrModuleDecl hsmodName id False + +findPositionFromImportsOrModuleDecl :: HasSrcSpan a => t -> (t -> a) -> Bool -> Maybe ((Int, Int), Int) +findPositionFromImportsOrModuleDecl hsField f hasImports = case getLoc (f hsField) of + OldRealSrcSpan s -> + let col = calcCol s + in Just ((srcLocLine (realSrcSpanEnd s), col), col) + _ -> Nothing + where calcCol s = if hasImports then srcLocCol (realSrcSpanStart s) - 1 else 0 + +-- | Find the position one after the last file-header pragma +-- Defaults to zero if there are no pragmas in file +findNextPragmaPosition :: T.Text -> Maybe ((Int, Int), Int) +findNextPragmaPosition contents = Just ((lineNumber, 0), 0) + where + lineNumber = afterLangPragma . afterOptsGhc $ afterShebang + afterLangPragma = afterPragma "LANGUAGE" contents' + afterOptsGhc = afterPragma "OPTIONS_GHC" contents' + afterShebang = lastLineWithPrefix (T.isPrefixOf "#!") contents' 0 + contents' = T.lines contents + +afterPragma :: T.Text -> [T.Text] -> Int -> Int +afterPragma name contents lineNum = lastLineWithPrefix (checkPragma name) contents lineNum + +lastLineWithPrefix :: (T.Text -> Bool) -> [T.Text] -> Int -> Int +lastLineWithPrefix p contents lineNum = max lineNum next + where + next = maybe lineNum succ $ listToMaybe . reverse $ findIndices p contents + +checkPragma :: T.Text -> T.Text -> Bool +checkPragma name = check + where + check l = isPragma l && getName l == name + getName l = T.take (T.length name) $ T.dropWhile isSpace $ T.drop 3 l + isPragma = T.isPrefixOf "{-#" + -- | Construct an import declaration with at most one symbol newImport :: T.Text -- ^ module name diff --git a/ghcide/src/Development/IDE/Plugin/Completions.hs b/ghcide/src/Development/IDE/Plugin/Completions.hs index 05f0b13837..e3753cb844 100644 --- a/ghcide/src/Development/IDE/Plugin/Completions.hs +++ b/ghcide/src/Development/IDE/Plugin/Completions.hs @@ -187,13 +187,14 @@ extendImportHandler' ideState ExtendImport {..} | Just fp <- uriToFilePath doc, nfp <- toNormalizedFilePath' fp = do - (ModSummaryResult {..}, ps) <- MaybeT $ liftIO $ + (ModSummaryResult {..}, ps, contents) <- MaybeT $ liftIO $ runAction "extend import" ideState $ runMaybeT $ do -- We want accurate edits, so do not use stale data here msr <- MaybeT $ use GetModSummaryWithoutTimestamps nfp ps <- MaybeT $ use GetAnnotatedParsedSource nfp - return (msr, ps) + (_, contents) <- MaybeT $ use GetFileContents nfp + return (msr, ps, contents) let df = ms_hspp_opts msrModSummary wantedModule = mkModuleName (T.unpack importName) wantedQual = mkModuleName . T.unpack <$> importQual @@ -209,7 +210,7 @@ extendImportHandler' ideState ExtendImport {..} it = case thingParent of Nothing -> newThing Just p -> p <> "(" <> newThing <> ")" - t <- liftMaybe $ snd <$> newImportToEdit n (astA ps) + t <- liftMaybe $ snd <$> newImportToEdit n (astA ps) (fromMaybe "" contents) return (nfp, WorkspaceEdit {_changes=Just (fromList [(doc,List [t])]), _documentChanges=Nothing, _changeAnnotations=Nothing}) | otherwise = mzero diff --git a/ghcide/test/data/import-placement/CommentAtTop.expected.hs b/ghcide/test/data/import-placement/CommentAtTop.expected.hs new file mode 100644 index 0000000000..2e7a43d73e --- /dev/null +++ b/ghcide/test/data/import-placement/CommentAtTop.expected.hs @@ -0,0 +1,9 @@ +module Test +( SomeData(..) +) where +import Data.Monoid + +-- | Some comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/CommentAtTop.hs b/ghcide/test/data/import-placement/CommentAtTop.hs new file mode 100644 index 0000000000..a811d70cfa --- /dev/null +++ b/ghcide/test/data/import-placement/CommentAtTop.hs @@ -0,0 +1,8 @@ +module Test +( SomeData(..) +) where + +-- | Some comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/CommentAtTopMultipleComments.expected.hs b/ghcide/test/data/import-placement/CommentAtTopMultipleComments.expected.hs new file mode 100644 index 0000000000..6589449194 --- /dev/null +++ b/ghcide/test/data/import-placement/CommentAtTopMultipleComments.expected.hs @@ -0,0 +1,12 @@ +module Test +( SomeData(..) +) where +import Data.Monoid + +-- | Another comment +data SomethingElse = SomethingElse + +-- | Some comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/CommentAtTopMultipleComments.hs b/ghcide/test/data/import-placement/CommentAtTopMultipleComments.hs new file mode 100644 index 0000000000..80b1e16359 --- /dev/null +++ b/ghcide/test/data/import-placement/CommentAtTopMultipleComments.hs @@ -0,0 +1,11 @@ +module Test +( SomeData(..) +) where + +-- | Another comment +data SomethingElse = SomethingElse + +-- | Some comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/CommentCurlyBraceAtTop.expected.hs b/ghcide/test/data/import-placement/CommentCurlyBraceAtTop.expected.hs new file mode 100644 index 0000000000..50a6954815 --- /dev/null +++ b/ghcide/test/data/import-placement/CommentCurlyBraceAtTop.expected.hs @@ -0,0 +1,9 @@ +module Test +( SomeData(..) +) where +import Data.Monoid + +{- Some comment -} +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/CommentCurlyBraceAtTop.hs b/ghcide/test/data/import-placement/CommentCurlyBraceAtTop.hs new file mode 100644 index 0000000000..dd4b0688c0 --- /dev/null +++ b/ghcide/test/data/import-placement/CommentCurlyBraceAtTop.hs @@ -0,0 +1,8 @@ +module Test +( SomeData(..) +) where + +{- Some comment -} +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/DataAtTop.expected.hs b/ghcide/test/data/import-placement/DataAtTop.expected.hs new file mode 100644 index 0000000000..d2698e963b --- /dev/null +++ b/ghcide/test/data/import-placement/DataAtTop.expected.hs @@ -0,0 +1,11 @@ +module Test +( SomeData(..) +) where +import Data.Monoid + +data Something = Something + +-- | some comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/DataAtTop.hs b/ghcide/test/data/import-placement/DataAtTop.hs new file mode 100644 index 0000000000..8840738a51 --- /dev/null +++ b/ghcide/test/data/import-placement/DataAtTop.hs @@ -0,0 +1,10 @@ +module Test +( SomeData(..) +) where + +data Something = Something + +-- | some comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/ImportAtTop.expected.hs b/ghcide/test/data/import-placement/ImportAtTop.expected.hs new file mode 100644 index 0000000000..1f05d361d7 --- /dev/null +++ b/ghcide/test/data/import-placement/ImportAtTop.expected.hs @@ -0,0 +1,14 @@ +module Test +( SomeData(..) +) where + +import Data.Char +import Data.Monoid + +{- Some multi + line comment +-} +class Semigroup a => SomeData a + +-- | a comment +instance SomeData All diff --git a/ghcide/test/data/import-placement/ImportAtTop.hs b/ghcide/test/data/import-placement/ImportAtTop.hs new file mode 100644 index 0000000000..f4aa6780e0 --- /dev/null +++ b/ghcide/test/data/import-placement/ImportAtTop.hs @@ -0,0 +1,13 @@ +module Test +( SomeData(..) +) where + +import Data.Char + +{- Some multi + line comment +-} +class Semigroup a => SomeData a + +-- | a comment +instance SomeData All diff --git a/ghcide/test/data/import-placement/LangPragmaModuleAtTop.expected.hs b/ghcide/test/data/import-placement/LangPragmaModuleAtTop.expected.hs new file mode 100644 index 0000000000..e7ea2779dd --- /dev/null +++ b/ghcide/test/data/import-placement/LangPragmaModuleAtTop.expected.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE OverloadedStrings #-} + +module Test where +import Data.Monoid + +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/LangPragmaModuleAtTop.hs b/ghcide/test/data/import-placement/LangPragmaModuleAtTop.hs new file mode 100644 index 0000000000..52ac5ac564 --- /dev/null +++ b/ghcide/test/data/import-placement/LangPragmaModuleAtTop.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE OverloadedStrings #-} + +module Test where + +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/LangPragmaModuleExplicitExports.expected.hs b/ghcide/test/data/import-placement/LangPragmaModuleExplicitExports.expected.hs new file mode 100644 index 0000000000..097c3d2c56 --- /dev/null +++ b/ghcide/test/data/import-placement/LangPragmaModuleExplicitExports.expected.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE OverloadedStrings #-} + +module Test +( SomeData(..) +) where +import Data.Monoid + +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/LangPragmaModuleExplicitExports.hs b/ghcide/test/data/import-placement/LangPragmaModuleExplicitExports.hs new file mode 100644 index 0000000000..e528c43343 --- /dev/null +++ b/ghcide/test/data/import-placement/LangPragmaModuleExplicitExports.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE OverloadedStrings #-} + +module Test +( SomeData(..) +) where + +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/LangPragmaModuleWithComment.expected.hs b/ghcide/test/data/import-placement/LangPragmaModuleWithComment.expected.hs new file mode 100644 index 0000000000..ad8e7aa4f1 --- /dev/null +++ b/ghcide/test/data/import-placement/LangPragmaModuleWithComment.expected.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE OverloadedStrings #-} + +module Test +( SomeData(..) +) where +import Data.Monoid + +-- comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/LangPragmaModuleWithComment.hs b/ghcide/test/data/import-placement/LangPragmaModuleWithComment.hs new file mode 100644 index 0000000000..bac9db1cd6 --- /dev/null +++ b/ghcide/test/data/import-placement/LangPragmaModuleWithComment.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE OverloadedStrings #-} + +module Test +( SomeData(..) +) where + +-- comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/LanguagePragmaAtTop.expected.hs b/ghcide/test/data/import-placement/LanguagePragmaAtTop.expected.hs new file mode 100644 index 0000000000..970f8dee59 --- /dev/null +++ b/ghcide/test/data/import-placement/LanguagePragmaAtTop.expected.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE OverloadedStrings #-} +import Data.Monoid + +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/LanguagePragmaAtTop.hs b/ghcide/test/data/import-placement/LanguagePragmaAtTop.hs new file mode 100644 index 0000000000..2d679bd537 --- /dev/null +++ b/ghcide/test/data/import-placement/LanguagePragmaAtTop.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE OverloadedStrings #-} + +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/LanguagePragmaAtTopWithComment.expected.hs b/ghcide/test/data/import-placement/LanguagePragmaAtTopWithComment.expected.hs new file mode 100644 index 0000000000..3e6fc76050 --- /dev/null +++ b/ghcide/test/data/import-placement/LanguagePragmaAtTopWithComment.expected.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE OverloadedStrings #-} +import Data.Monoid + +-- | comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/LanguagePragmaAtTopWithComment.hs b/ghcide/test/data/import-placement/LanguagePragmaAtTopWithComment.hs new file mode 100644 index 0000000000..df1f85126b --- /dev/null +++ b/ghcide/test/data/import-placement/LanguagePragmaAtTopWithComment.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE OverloadedStrings #-} + +-- | comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/LanguagePragmasThenShebangs.expected.hs b/ghcide/test/data/import-placement/LanguagePragmasThenShebangs.expected.hs new file mode 100644 index 0000000000..c3efb90b68 --- /dev/null +++ b/ghcide/test/data/import-placement/LanguagePragmasThenShebangs.expected.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -Wall #-} +#! /usr/bin/env nix-shell +#! nix-shell --pure -i runghc -p "haskellPackages.ghcWithPackages (hp: with hp; [ turtle ])" +import Data.Monoid + +-- some comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/LanguagePragmasThenShebangs.hs b/ghcide/test/data/import-placement/LanguagePragmasThenShebangs.hs new file mode 100644 index 0000000000..916e465856 --- /dev/null +++ b/ghcide/test/data/import-placement/LanguagePragmasThenShebangs.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -Wall #-} +#! /usr/bin/env nix-shell +#! nix-shell --pure -i runghc -p "haskellPackages.ghcWithPackages (hp: with hp; [ turtle ])" + +-- some comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/ModuleDeclAndImports.expected.hs b/ghcide/test/data/import-placement/ModuleDeclAndImports.expected.hs new file mode 100644 index 0000000000..b9492d84ba --- /dev/null +++ b/ghcide/test/data/import-placement/ModuleDeclAndImports.expected.hs @@ -0,0 +1,10 @@ +module Test +( SomeData(..) +) where +import Data.Char +import Data.Array +import Data.Monoid + +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/ModuleDeclAndImports.hs b/ghcide/test/data/import-placement/ModuleDeclAndImports.hs new file mode 100644 index 0000000000..5cef735e54 --- /dev/null +++ b/ghcide/test/data/import-placement/ModuleDeclAndImports.hs @@ -0,0 +1,9 @@ +module Test +( SomeData(..) +) where +import Data.Char +import Data.Array + +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/MultiLineCommentAtTop.expected.hs b/ghcide/test/data/import-placement/MultiLineCommentAtTop.expected.hs new file mode 100644 index 0000000000..4c96510899 --- /dev/null +++ b/ghcide/test/data/import-placement/MultiLineCommentAtTop.expected.hs @@ -0,0 +1,11 @@ +module Test +( SomeData(..) +) where +import Data.Monoid + +{- Some multi + line comment +-} +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/MultiLineCommentAtTop.hs b/ghcide/test/data/import-placement/MultiLineCommentAtTop.hs new file mode 100644 index 0000000000..8cf400d448 --- /dev/null +++ b/ghcide/test/data/import-placement/MultiLineCommentAtTop.hs @@ -0,0 +1,10 @@ +module Test +( SomeData(..) +) where + +{- Some multi + line comment +-} +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/MultipleImportsAtTop.expected.hs b/ghcide/test/data/import-placement/MultipleImportsAtTop.expected.hs new file mode 100644 index 0000000000..9a7d3d5214 --- /dev/null +++ b/ghcide/test/data/import-placement/MultipleImportsAtTop.expected.hs @@ -0,0 +1,14 @@ +module Test +( SomeData(..) +) where + +import Data.Char +import Data.Bool +import Data.Eq +import Data.Monoid + +-- | A comment +class Semigroup a => SomeData a + +-- | another comment +instance SomeData All diff --git a/ghcide/test/data/import-placement/MultipleImportsAtTop.hs b/ghcide/test/data/import-placement/MultipleImportsAtTop.hs new file mode 100644 index 0000000000..1eab2c5685 --- /dev/null +++ b/ghcide/test/data/import-placement/MultipleImportsAtTop.hs @@ -0,0 +1,13 @@ +module Test +( SomeData(..) +) where + +import Data.Char +import Data.Bool +import Data.Eq + +-- | A comment +class Semigroup a => SomeData a + +-- | another comment +instance SomeData All diff --git a/ghcide/test/data/import-placement/MultipleLanguagePragmasNoModuleDeclaration.expected.hs b/ghcide/test/data/import-placement/MultipleLanguagePragmasNoModuleDeclaration.expected.hs new file mode 100644 index 0000000000..94ed4397a4 --- /dev/null +++ b/ghcide/test/data/import-placement/MultipleLanguagePragmasNoModuleDeclaration.expected.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE RankNTypes #-} +import Data.Monoid + +-- some comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/MultipleLanguagePragmasNoModuleDeclaration.hs b/ghcide/test/data/import-placement/MultipleLanguagePragmasNoModuleDeclaration.hs new file mode 100644 index 0000000000..352c2b2763 --- /dev/null +++ b/ghcide/test/data/import-placement/MultipleLanguagePragmasNoModuleDeclaration.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE RankNTypes #-} + +-- some comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/NewTypeAtTop.expected.hs b/ghcide/test/data/import-placement/NewTypeAtTop.expected.hs new file mode 100644 index 0000000000..27ec825a79 --- /dev/null +++ b/ghcide/test/data/import-placement/NewTypeAtTop.expected.hs @@ -0,0 +1,11 @@ +module Test +( SomeData(..) +) where +import Data.Monoid + +newtype Something = S { foo :: Int } + +-- | a comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/NewTypeAtTop.hs b/ghcide/test/data/import-placement/NewTypeAtTop.hs new file mode 100644 index 0000000000..64a49358d9 --- /dev/null +++ b/ghcide/test/data/import-placement/NewTypeAtTop.hs @@ -0,0 +1,10 @@ +module Test +( SomeData(..) +) where + +newtype Something = S { foo :: Int } + +-- | a comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/NoExplicitExportCommentAtTop.expected.hs b/ghcide/test/data/import-placement/NoExplicitExportCommentAtTop.expected.hs new file mode 100644 index 0000000000..6388cb99da --- /dev/null +++ b/ghcide/test/data/import-placement/NoExplicitExportCommentAtTop.expected.hs @@ -0,0 +1,7 @@ +module Test where +import Data.Monoid + +-- | a comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/NoExplicitExportCommentAtTop.hs b/ghcide/test/data/import-placement/NoExplicitExportCommentAtTop.hs new file mode 100644 index 0000000000..761ea388b1 --- /dev/null +++ b/ghcide/test/data/import-placement/NoExplicitExportCommentAtTop.hs @@ -0,0 +1,6 @@ +module Test where + +-- | a comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/NoExplicitExports.expected.hs b/ghcide/test/data/import-placement/NoExplicitExports.expected.hs new file mode 100644 index 0000000000..fb92a8309e --- /dev/null +++ b/ghcide/test/data/import-placement/NoExplicitExports.expected.hs @@ -0,0 +1,8 @@ +module Test where +import Data.Monoid + +newtype Something = S { foo :: Int } + +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/NoExplicitExports.hs b/ghcide/test/data/import-placement/NoExplicitExports.hs new file mode 100644 index 0000000000..8515a4ff35 --- /dev/null +++ b/ghcide/test/data/import-placement/NoExplicitExports.hs @@ -0,0 +1,7 @@ +module Test where + +newtype Something = S { foo :: Int } + +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/NoModuleDeclaration.expected.hs b/ghcide/test/data/import-placement/NoModuleDeclaration.expected.hs new file mode 100644 index 0000000000..2136db9018 --- /dev/null +++ b/ghcide/test/data/import-placement/NoModuleDeclaration.expected.hs @@ -0,0 +1,7 @@ +import Data.Monoid +newtype Something = S { foo :: Int } + +-- | a comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/NoModuleDeclaration.hs b/ghcide/test/data/import-placement/NoModuleDeclaration.hs new file mode 100644 index 0000000000..5173bc31a6 --- /dev/null +++ b/ghcide/test/data/import-placement/NoModuleDeclaration.hs @@ -0,0 +1,6 @@ +newtype Something = S { foo :: Int } + +-- | a comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/NoModuleDeclarationCommentAtTop.expected.hs b/ghcide/test/data/import-placement/NoModuleDeclarationCommentAtTop.expected.hs new file mode 100644 index 0000000000..9336469265 --- /dev/null +++ b/ghcide/test/data/import-placement/NoModuleDeclarationCommentAtTop.expected.hs @@ -0,0 +1,5 @@ +import Data.Monoid +-- a comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/NoModuleDeclarationCommentAtTop.hs b/ghcide/test/data/import-placement/NoModuleDeclarationCommentAtTop.hs new file mode 100644 index 0000000000..8727beedf1 --- /dev/null +++ b/ghcide/test/data/import-placement/NoModuleDeclarationCommentAtTop.hs @@ -0,0 +1,4 @@ +-- a comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/PragmasAndShebangsNoComment.expected.hs b/ghcide/test/data/import-placement/PragmasAndShebangsNoComment.expected.hs new file mode 100644 index 0000000000..7c0ce68d8f --- /dev/null +++ b/ghcide/test/data/import-placement/PragmasAndShebangsNoComment.expected.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -Wall #-} +#! /usr/bin/env nix-shell +#! nix-shell --pure -i runghc -p "haskellPackages.ghcWithPackages (hp: with hp; [ turtle ])" +import Data.Monoid + +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/PragmasAndShebangsNoComment.hs b/ghcide/test/data/import-placement/PragmasAndShebangsNoComment.hs new file mode 100644 index 0000000000..bdd2e9b69b --- /dev/null +++ b/ghcide/test/data/import-placement/PragmasAndShebangsNoComment.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -Wall #-} +#! /usr/bin/env nix-shell +#! nix-shell --pure -i runghc -p "haskellPackages.ghcWithPackages (hp: with hp; [ turtle ])" + +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/PragmasShebangsAndModuleDecl.expected.hs b/ghcide/test/data/import-placement/PragmasShebangsAndModuleDecl.expected.hs new file mode 100644 index 0000000000..a582ff69ac --- /dev/null +++ b/ghcide/test/data/import-placement/PragmasShebangsAndModuleDecl.expected.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -Wall #-} +#! /usr/bin/env nix-shell +#! nix-shell --pure -i runghc -p "haskellPackages.ghcWithPackages (hp: with hp; [ turtle ])" + +module Test where +import Data.Monoid + +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/PragmasShebangsAndModuleDecl.hs b/ghcide/test/data/import-placement/PragmasShebangsAndModuleDecl.hs new file mode 100644 index 0000000000..e1eac4118d --- /dev/null +++ b/ghcide/test/data/import-placement/PragmasShebangsAndModuleDecl.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -Wall #-} +#! /usr/bin/env nix-shell +#! nix-shell --pure -i runghc -p "haskellPackages.ghcWithPackages (hp: with hp; [ turtle ])" + +module Test where + +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/PragmasShebangsModuleExplicitExports.expected.hs b/ghcide/test/data/import-placement/PragmasShebangsModuleExplicitExports.expected.hs new file mode 100644 index 0000000000..03271ccad2 --- /dev/null +++ b/ghcide/test/data/import-placement/PragmasShebangsModuleExplicitExports.expected.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -Wall #-} +#! /usr/bin/env nix-shell +#! nix-shell --pure -i runghc -p "haskellPackages.ghcWithPackages (hp: with hp; [ turtle ])" + +module Test +( SomeData(..) +) where +import Data.Monoid + +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/PragmasShebangsModuleExplicitExports.hs b/ghcide/test/data/import-placement/PragmasShebangsModuleExplicitExports.hs new file mode 100644 index 0000000000..b59e9b22de --- /dev/null +++ b/ghcide/test/data/import-placement/PragmasShebangsModuleExplicitExports.hs @@ -0,0 +1,12 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -Wall #-} +#! /usr/bin/env nix-shell +#! nix-shell --pure -i runghc -p "haskellPackages.ghcWithPackages (hp: with hp; [ turtle ])" + +module Test +( SomeData(..) +) where + +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/PragmasThenShebangsMultilineComment.expected.hs b/ghcide/test/data/import-placement/PragmasThenShebangsMultilineComment.expected.hs new file mode 100644 index 0000000000..95adbd87cd --- /dev/null +++ b/ghcide/test/data/import-placement/PragmasThenShebangsMultilineComment.expected.hs @@ -0,0 +1,12 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -Wall #-} +#! /usr/bin/env nix-shell +#! nix-shell --pure -i runghc -p "haskellPackages.ghcWithPackages (hp: with hp; [ turtle ])" +import Data.Monoid + +{- | some multiline + comment + ... -} +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/PragmasThenShebangsMultilineComment.hs b/ghcide/test/data/import-placement/PragmasThenShebangsMultilineComment.hs new file mode 100644 index 0000000000..5f56f1c390 --- /dev/null +++ b/ghcide/test/data/import-placement/PragmasThenShebangsMultilineComment.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -Wall #-} +#! /usr/bin/env nix-shell +#! nix-shell --pure -i runghc -p "haskellPackages.ghcWithPackages (hp: with hp; [ turtle ])" + +{- | some multiline + comment + ... -} +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/TwoDashOnlyComment.expected.hs b/ghcide/test/data/import-placement/TwoDashOnlyComment.expected.hs new file mode 100644 index 0000000000..e2c4f7c230 --- /dev/null +++ b/ghcide/test/data/import-placement/TwoDashOnlyComment.expected.hs @@ -0,0 +1,9 @@ +module Test +( SomeData(..) +) where +import Data.Monoid + +-- no vertical bar comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/data/import-placement/TwoDashOnlyComment.hs b/ghcide/test/data/import-placement/TwoDashOnlyComment.hs new file mode 100644 index 0000000000..87749ec8d2 --- /dev/null +++ b/ghcide/test/data/import-placement/TwoDashOnlyComment.hs @@ -0,0 +1,8 @@ +module Test +( SomeData(..) +) where + +-- no vertical bar comment +class Semigroup a => SomeData a + +instance SomeData All diff --git a/ghcide/test/exe/Main.hs b/ghcide/test/exe/Main.hs index ac087499bb..800027c569 100644 --- a/ghcide/test/exe/Main.hs +++ b/ghcide/test/exe/Main.hs @@ -60,10 +60,11 @@ import Development.Shake (getDirectoryFilesIO) import qualified Experiments as Bench import Ide.Plugin.Config import Language.LSP.Test -import Language.LSP.Types hiding - (mkRange, SemanticTokenAbsolute (length, line), - SemanticTokenRelative (length), - SemanticTokensEdit (_start)) +import Language.LSP.Types hiding + (SemanticTokenAbsolute (length, line), + SemanticTokenRelative (length), + SemanticTokensEdit (_start), + mkRange) import Language.LSP.Types.Capabilities import qualified Language.LSP.Types.Lens as Lsp (diagnostics, message, @@ -132,11 +133,11 @@ main = do waitForProgressBegin closeDoc doc waitForProgressDone + , codeActionTests , initializeResponseTests , completionTests , cppTests , diagnosticTests - , codeActionTests , codeLensesTests , outlineTests , highlightTests @@ -730,10 +731,11 @@ cancellationTemplate (edit, undoEdit) mbKey = testCase (maybe "-" fst mbKey) $ r codeActionTests :: TestTree codeActionTests = testGroup "code actions" - [ renameActionTests + [ insertImportTests + , extendImportTests + , renameActionTests , typeWildCardActionTests , removeImportTests - , extendImportTests , suggestImportClassMethodTests , suggestImportTests , suggestHideShadowTests @@ -788,6 +790,51 @@ watchedFilesTests = testGroup "watched files" -- TODO add a test for didChangeWorkspaceFolder ] +insertImportTests :: TestTree +insertImportTests = testGroup "insert import" + [ checkImport "above comment at top of module" "CommentAtTop.hs" "CommentAtTop.expected.hs" "import Data.Monoid" + , checkImport "above multiple comments below" "CommentAtTopMultipleComments.hs" "CommentAtTopMultipleComments.expected.hs" "import Data.Monoid" + , checkImport "above curly brace comment" "CommentCurlyBraceAtTop.hs" "CommentCurlyBraceAtTop.expected.hs" "import Data.Monoid" + , checkImport "above multi-line comment" "MultiLineCommentAtTop.hs" "MultiLineCommentAtTop.expected.hs" "import Data.Monoid" + , checkImport "above comment with no module explicit exports" "NoExplicitExportCommentAtTop.hs" "NoExplicitExportCommentAtTop.expected.hs" "import Data.Monoid" + , checkImport "above two-dash comment with no pipe" "TwoDashOnlyComment.hs" "TwoDashOnlyComment.expected.hs" "import Data.Monoid" + , checkImport "above comment with no (module .. where) decl" "NoModuleDeclarationCommentAtTop.hs" "NoModuleDeclarationCommentAtTop.expected.hs" "import Data.Monoid" + , checkImport "comment not at top with no (module .. where) decl" "NoModuleDeclaration.hs" "NoModuleDeclaration.expected.hs" "import Data.Monoid" + , checkImport "comment not at top (data dec is)" "DataAtTop.hs" "DataAtTop.expected.hs" "import Data.Monoid" + , checkImport "comment not at top (newtype is)" "NewTypeAtTop.hs" "NewTypeAtTop.expected.hs" "import Data.Monoid" + , checkImport "with no explicit module exports" "NoExplicitExports.hs" "NoExplicitExports.expected.hs" "import Data.Monoid" + , checkImport "add to correctly placed exisiting import" "ImportAtTop.hs" "ImportAtTop.expected.hs" "import Data.Monoid" + , checkImport "add to multiple correctly placed exisiting imports" "MultipleImportsAtTop.hs" "MultipleImportsAtTop.expected.hs" "import Data.Monoid" + , checkImport "with language pragma at top of module" "LangPragmaModuleAtTop.hs" "LangPragmaModuleAtTop.expected.hs" "import Data.Monoid" + , checkImport "with language pragma and explicit module exports" "LangPragmaModuleWithComment.hs" "LangPragmaModuleWithComment.expected.hs" "import Data.Monoid" + , checkImport "with language pragma at top and no module declaration" "LanguagePragmaAtTop.hs" "LanguagePragmaAtTop.expected.hs" "import Data.Monoid" + , checkImport "with multiple lang pragmas and no module declaration" "MultipleLanguagePragmasNoModuleDeclaration.hs" "MultipleLanguagePragmasNoModuleDeclaration.expected.hs" "import Data.Monoid" + , checkImport "with pragmas and shebangs" "LanguagePragmasThenShebangs.hs" "LanguagePragmasThenShebangs.expected.hs" "import Data.Monoid" + , checkImport "with pragmas and shebangs but no comment at top" "PragmasAndShebangsNoComment.hs" "PragmasAndShebangsNoComment.expected.hs" "import Data.Monoid" + , checkImport "module decl no exports under pragmas and shebangs" "PragmasShebangsAndModuleDecl.hs" "PragmasShebangsAndModuleDecl.expected.hs" "import Data.Monoid" + , checkImport "module decl with explicit import under pragmas and shebangs" "PragmasShebangsModuleExplicitExports.hs" "PragmasShebangsModuleExplicitExports.expected.hs" "import Data.Monoid" + , checkImport "module decl and multiple imports" "ModuleDeclAndImports.hs" "ModuleDeclAndImports.expected.hs" "import Data.Monoid" + ] + +checkImport :: String -> FilePath -> FilePath -> T.Text -> TestTree +checkImport testComment originalPath expectedPath action = + testSessionWithExtraFiles "import-placement" testComment $ \dir -> + check (dir originalPath) (dir expectedPath) action + where + check :: FilePath -> FilePath -> T.Text -> Session () + check originalPath expectedPath action = do + oSrc <- liftIO $ readFileUtf8 originalPath + eSrc <- liftIO $ readFileUtf8 expectedPath + originalDoc <- createDoc originalPath "haskell" oSrc + _ <- waitForDiagnostics + shouldBeDoc <- createDoc expectedPath "haskell" eSrc + actionsOrCommands <- getAllCodeActions originalDoc + chosenAction <- liftIO $ pickActionWithTitle action actionsOrCommands + executeCodeAction chosenAction + originalDocAfterAction <- documentContents originalDoc + shouldBeDocContents <- documentContents shouldBeDoc + liftIO $ T.replace "\r\n" "\n" shouldBeDocContents @=? T.replace "\r\n" "\n" originalDocAfterAction + renameActionTests :: TestTree renameActionTests = testGroup "rename actions" [ testSession "change to local variable name" $ do @@ -1545,15 +1592,15 @@ suggestImportClassMethodTests = [ testSession "via parent" $ template' "import Data.Semigroup (Semigroup(stimes))" - (Range (Position 5 2) (Position 5 8)), + (Range (Position 4 2) (Position 4 8)), testSession "top level" $ template' "import Data.Semigroup (stimes)" - (Range (Position 5 2) (Position 5 8)), + (Range (Position 4 2) (Position 4 8)), testSession "all" $ template' "import Data.Semigroup" - (Range (Position 5 2) (Position 5 8)) + (Range (Position 4 2) (Position 4 8)) ], testGroup "extend" @@ -1601,7 +1648,7 @@ suggestImportClassMethodTests = executeCodeAction $ fromJust $ find (\CodeAction {_title} -> _title == executeTitle) actions' content <- documentContents doc liftIO $ T.unlines (expectedContent <> decls) @=? content - template' executeTitle range = let c = ["module A where", ""] in template c range executeTitle $ c <> [executeTitle] + template' executeTitle range = let c = ["module A where"] in template c range executeTitle $ c <> [executeTitle] suggestImportTests :: TestTree suggestImportTests = testGroup "suggest import actions"