ghcide-0.4.0: The core of an IDE

Safe HaskellNone
LanguageHaskell2010

Development.IDE.Types.Options

Description

Options

Synopsis

Documentation

data IdeOptions Source #

Constructors

IdeOptions 

Fields

  • optPreprocessor :: ParsedSource -> IdePreprocessedSource

    Preprocessor to run over all parsed source trees, generating a list of warnings and a list of errors, along with a new parse tree.

  • optGhcSession :: Action IdeGhcSession

    Setup a GHC session for a given file, e.g. Foo.hs. For the same ComponentOptions from hie-bios, the resulting function will be applied once per file. It is desirable that many files get the same HscEnvEq, so that more IDE features work.

  • optPkgLocationOpts :: IdePkgLocationOptions

    How to locate source and .hie files given a module name.

  • optExtensions :: [String]

    File extensions to search for code, defaults to Haskell sources (including .hs)

  • optThreads :: Int

    Number of threads to use. Use 0 for number of threads on the machine.

  • optShakeFiles :: Maybe FilePath

    Directory where the shake database should be stored. For ghcide this is always set to Nothing for now meaning we keep everything in memory but the daml CLI compiler uses this for incremental builds.

  • optShakeProfiling :: Maybe FilePath

    Set to Just to create a directory of profiling reports.

  • optTesting :: IdeTesting

    Whether to enable additional lsp messages used by the test suite for checking invariants

  • optReportProgress :: IdeReportProgress

    Whether to report progress during long operations.

  • optLanguageSyntax :: String

    the ```language to use

  • optNewColonConvention :: Bool

    whether to use new colon convention

  • optKeywords :: [Text]

    keywords used for completions. These are customizable since DAML has a different set of keywords than Haskell.

  • optDefer :: IdeDefer

    Whether to defer type errors, typed holes and out of scope variables. Deferral allows the IDE to continue to provide features such as diagnostics and go-to-definition, in situations in which they would become unavailable because of the presence of type errors, holes or unbound variables.

  • optCheckProject :: CheckProject

    Whether to typecheck the entire project on load

  • optCheckParents :: CheckParents

    When to typecheck reverse dependencies of a file

  • optHaddockParse :: OptHaddockParse

    Whether to return result of parsing module with Opt_Haddock. Otherwise, return the result of parsing without Opt_Haddock, so that the parsed module contains the result of Opt_KeepRawTokenStream, which might be necessary for hlint.

  • optCustomDynFlags :: DynFlags -> DynFlags

    If given, it will be called right after setting up a new cradle, allowing to customize the Ghc options used

data IdePreprocessedSource Source #

Constructors

IdePreprocessedSource 

Fields

newtype IdeDefer Source #

Constructors

IdeDefer Bool 

newtype IdeTesting Source #

Constructors

IdeTesting Bool 

data IdePkgLocationOptions Source #

The set of options used to locate files belonging to external packages.

Constructors

IdePkgLocationOptions 

Fields

type IdeResult v = ([FileDiagnostic], Maybe v) Source #

The result of an IDE operation. Warnings and errors are in the Diagnostic, and a value is in the Maybe. For operations that throw an error you expect a non-empty list of diagnostics, at least one of which is an error, and a Nothing. For operations that succeed you expect perhaps some warnings and a Just. For operations that depend on other failing operations you may get empty diagnostics and a Nothing, to indicate this phase throws no fresh errors but still failed.

A rule on a file should only return diagnostics for that given file. It should not propagate diagnostic errors through multiple phases.

data IdeGhcSession Source #

Constructors

IdeGhcSession 

Fields

data LspConfig Source #

Instances
Eq LspConfig Source # 
Instance details

Defined in Development.IDE.Types.Options

Ord LspConfig Source # 
Instance details

Defined in Development.IDE.Types.Options

Show LspConfig Source # 
Instance details

Defined in Development.IDE.Types.Options

Generic LspConfig Source # 
Instance details

Defined in Development.IDE.Types.Options

Associated Types

type Rep LspConfig :: Type -> Type #

ToJSON LspConfig Source # 
Instance details

Defined in Development.IDE.Types.Options

FromJSON LspConfig Source # 
Instance details

Defined in Development.IDE.Types.Options

type Rep LspConfig Source # 
Instance details

Defined in Development.IDE.Types.Options

type Rep LspConfig = D1 (MetaData "LspConfig" "Development.IDE.Types.Options" "ghcide-0.4.0-98cFz095V7v2i8ymOuBUUo" False) (C1 (MetaCons "LspConfig" PrefixI True) (S1 (MetaSel (Just "checkParents") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CheckParents) :*: S1 (MetaSel (Just "checkProject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CheckProject)))

data CheckParents Source #

Instances
Eq CheckParents Source # 
Instance details

Defined in Development.IDE.Types.Options

Ord CheckParents Source # 
Instance details

Defined in Development.IDE.Types.Options

Show CheckParents Source # 
Instance details

Defined in Development.IDE.Types.Options

Generic CheckParents Source # 
Instance details

Defined in Development.IDE.Types.Options

Associated Types

type Rep CheckParents :: Type -> Type #

ToJSON CheckParents Source # 
Instance details

Defined in Development.IDE.Types.Options

FromJSON CheckParents Source # 
Instance details

Defined in Development.IDE.Types.Options

type Rep CheckParents Source # 
Instance details

Defined in Development.IDE.Types.Options

type Rep CheckParents = D1 (MetaData "CheckParents" "Development.IDE.Types.Options" "ghcide-0.4.0-98cFz095V7v2i8ymOuBUUo" False) ((C1 (MetaCons "NeverCheck" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CheckOnClose" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CheckOnSaveAndClose" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AlwaysCheck" PrefixI False) (U1 :: Type -> Type)))

data OptHaddockParse Source #