Skip to content

Commit

Permalink
Merge pull request #687 from jneira/cpplugins
Browse files Browse the repository at this point in the history
Add plugins conditionally at compile time
  • Loading branch information
jneira authored Dec 18, 2020
2 parents e4f677e + 4c57384 commit 4ea51f6
Show file tree
Hide file tree
Showing 3 changed files with 292 additions and 90 deletions.
63 changes: 1 addition & 62 deletions exe/Main.hs
Original file line number Diff line number Diff line change
@@ -1,75 +1,14 @@
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
-- SPDX-License-Identifier: Apache-2.0
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Main(main) where

import Ide.Arguments (Arguments (..), LspArguments (..),
getArguments)
import Ide.Main (defaultMain)
import Ide.Types (IdePlugins)
import Plugins

-- haskell-language-server plugins

import Ide.Plugin.Eval as Eval
import Ide.Plugin.Example as Example
import Ide.Plugin.Example2 as Example2
import Ide.Plugin.Floskell as Floskell
import Ide.Plugin.Fourmolu as Fourmolu
import Ide.Plugin.GhcIde as GhcIde
import Ide.Plugin.ExplicitImports as ExplicitImports
import Ide.Plugin.Ormolu as Ormolu
import Ide.Plugin.Retrie as Retrie
import Ide.Plugin.StylishHaskell as StylishHaskell
import Ide.Plugin.Tactic as Tactic
import Ide.Plugin.Hlint as Hlint
#if AGPL
import Ide.Plugin.Brittany as Brittany
#endif
import Ide.Plugin (pluginDescToIdePlugins)
import Ide.Plugin.ModuleName as ModuleName
import Ide.Plugin.Pragmas as Pragmas


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

-- | The plugins configured for use in this instance of the language
-- server.
-- These can be freely added or removed to tailor the available
-- features of the server.

idePlugins :: Bool -> IdePlugins
idePlugins includeExamples = pluginDescToIdePlugins allPlugins
where
allPlugins = if includeExamples
then basePlugins ++ examplePlugins
else basePlugins
basePlugins =
[ GhcIde.descriptor "ghcide"
, Pragmas.descriptor "pragmas"
, Floskell.descriptor "floskell"
, Fourmolu.descriptor "fourmolu"
, Tactic.descriptor "tactic"
-- , genericDescriptor "generic"
-- , ghcmodDescriptor "ghcmod"
, Ormolu.descriptor "ormolu"
, StylishHaskell.descriptor "stylish-haskell"
, Retrie.descriptor "retrie"
#if AGPL
, Brittany.descriptor "brittany"
#endif
, Eval.descriptor "eval"
, ExplicitImports.descriptor "importLens"
, ModuleName.descriptor "moduleName"
, Hlint.descriptor "hlint"
]
examplePlugins =
[Example.descriptor "eg"
,Example2.descriptor "eg2"
]

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

main :: IO ()
main = do
Expand Down
120 changes: 120 additions & 0 deletions exe/Plugins.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,120 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module Plugins where

import Ide.Types (IdePlugins)
import Ide.Plugin (pluginDescToIdePlugins)

-- fixed plugins
import Ide.Plugin.Example as Example
import Ide.Plugin.Example2 as Example2
import Ide.Plugin.GhcIde as GhcIde

-- haskell-language-server optional plugins

#if eval
import Ide.Plugin.Eval as Eval
#endif

#if importLens
import Ide.Plugin.ExplicitImports as ExplicitImports
#endif

#if retrie
import Ide.Plugin.Retrie as Retrie
#endif

#if tactic
import Ide.Plugin.Tactic as Tactic
#endif

#if hlint
import Ide.Plugin.Hlint as Hlint
#endif

#if moduleName
import Ide.Plugin.ModuleName as ModuleName
#endif

#if pragmas
import Ide.Plugin.Pragmas as Pragmas
#endif

-- formatters

#if floskell
import Ide.Plugin.Floskell as Floskell
#endif

#if fourmolu
import Ide.Plugin.Fourmolu as Fourmolu
#endif

#if ormolu
import Ide.Plugin.Ormolu as Ormolu
#endif

#if stylishHaskell
import Ide.Plugin.StylishHaskell as StylishHaskell
#endif

#if AGPL && brittany
import Ide.Plugin.Brittany as Brittany
#endif

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

-- | The plugins configured for use in this instance of the language
-- server.
-- These can be freely added or removed to tailor the available
-- features of the server.

idePlugins :: Bool -> IdePlugins
idePlugins includeExamples = pluginDescToIdePlugins allPlugins
where
allPlugins = if includeExamples
then basePlugins ++ examplePlugins
else basePlugins
basePlugins =
[ GhcIde.descriptor "ghcide"
#if pragmas
, Pragmas.descriptor "pragmas"
#endif
#if floskell
, Floskell.descriptor "floskell"
#endif
#if fourmolu
, Fourmolu.descriptor "fourmolu"
#endif
#if tactic
, Tactic.descriptor "tactic"
#endif
#if ormolu
, Ormolu.descriptor "ormolu"
#endif
#if stylishHaskell
, StylishHaskell.descriptor "stylish-haskell"
#endif
#if retrie
, Retrie.descriptor "retrie"
#endif
#if AGPL && brittany
, Brittany.descriptor "brittany"
#endif
#if eval
, Eval.descriptor "eval"
#endif
#if importLens
, ExplicitImports.descriptor "importLens"
#endif
#if moduleName
, ModuleName.descriptor "moduleName"
#endif
#if hlint
, Hlint.descriptor "hlint"
#endif
]
examplePlugins =
[Example.descriptor "eg"
,Example2.descriptor "eg2"
]
Loading

0 comments on commit 4ea51f6

Please sign in to comment.