Add back descriptions to plugin modules as haddocks

This commit is contained in:
Luke Lau 2019-12-23 01:42:25 +00:00
parent 7ca12934dd
commit 6da43ab047
11 changed files with 22 additions and 9 deletions

View File

@ -2,6 +2,9 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
-- | apply-refact applies refactorings specified by the refact package. It is
-- currently integrated into hlint to enable the automatic application of
-- suggestions.
module Haskell.Ide.Engine.Plugin.ApplyRefact where
import Control.Arrow

View File

@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
-- | Brittany is a tool to format source code.
module Haskell.Ide.Engine.Plugin.Brittany where
import Control.Lens

View File

@ -2,6 +2,7 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
-- | An example of writing an HIE plugin
module Haskell.Ide.Engine.Plugin.Example2 where
import Control.Lens

View File

@ -1,5 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
-- | A flexible Haskell source code pretty printer.
module Haskell.Ide.Engine.Plugin.Floskell
( floskellDescriptor
)

View File

@ -5,7 +5,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
-- Generic actions which require a typechecked module
-- | Generic actions which require a typechecked module
module Haskell.Ide.Engine.Plugin.Generic where
import Control.Lens hiding (cons, children)

View File

@ -1,8 +1,9 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleContexts #-}
-- | Provides haddock documentation on hover.
module Haskell.Ide.Engine.Plugin.Haddock where
import Control.Monad.State

View File

@ -3,7 +3,7 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
-- Simple example plugin showing how easy it is to make a plugin, using the operations from
-- | Simple example plugin showing how easy it is to make a plugin, using the operations from
-- http://www.haskellforall.com/2018/10/detailed-walkthrough-for-beginner.html
module Haskell.Ide.Engine.Plugin.HfaAlign where
@ -20,7 +20,6 @@ import qualified Language.Haskell.LSP.Types.Lens as J
import Data.Text (Text)
import qualified Data.Text
-- import qualified Data.Text.IO
import qualified Safe
-- ---------------------------------------------------------------------
@ -110,5 +109,3 @@ adjustText oldText = newText
newText = Data.Text.unlines newLines
-- main :: IO ()
-- main = Data.Text.IO.interact adjustText

View File

@ -2,6 +2,9 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE LambdaCase #-}
-- | A tool for extending the import list of a Haskell source file.
-- Provides code actions and commands.
module Haskell.Ide.Engine.Plugin.HsImport where
import Control.Lens.Operators
@ -370,8 +373,8 @@ codeActionProvider plId docId _ context = do
codeActions = case termType impDiagnostic of
Hiding _ -> [] {- If we are hiding an import, we can not import
a module hiding everything from it. -}
-- Simple import, import the whole module
Import _ -> [mkImportAction moduleName impDiagnostic Nothing]
-- ^ Simple import, import the whole module
++ importListActions
-- | Retrieve the function signature of a term such as
@ -433,7 +436,7 @@ codeActionProvider plId docId _ context = do
<> modName
<> case termType importDiagnostic of
Hiding _ -> "hiding"
-- ^ Note, that it must never happen
-- Note, that it must never happen
-- in combination with `symbolType == Nothing`
Import _ -> ""
<> case symbolType of

View File

@ -1,7 +1,8 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NamedFieldPuns #-}
-- | Integration with Liquid Haskell with diagnostics and hover information
module Haskell.Ide.Engine.Plugin.Liquid where
import Control.Concurrent.Async.Lifted

View File

@ -4,6 +4,9 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TupleSections #-}
-- | Commands and code actions for adding package dependencies into .cabal and
-- package.yaml files
module Haskell.Ide.Engine.Plugin.Package where
import Haskell.Ide.Engine.MonadTypes

View File

@ -1,6 +1,8 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
-- | Provides code actions to add missing pragmas (whenever GHC suggests to)
module Haskell.Ide.Engine.Plugin.Pragmas where
import Control.Lens