{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
module Development.IDE.Types.Options
( IdeOptions(..)
, IdePreprocessedSource(..)
, IdeReportProgress(..)
, IdeDefer(..)
, IdeTesting(..)
, IdeOTMemoryProfiling(..)
, clientSupportsProgress
, IdePkgLocationOptions(..)
, defaultIdeOptions
, IdeResult
, IdeGhcSession(..)
, LspConfig(..)
, defaultLspConfig
, CheckProject(..)
, CheckParents(..)
, OptHaddockParse(..)
) where
import Development.Shake
import Development.IDE.GHC.Util
import GHC hiding (parseModule, typecheckModule)
import GhcPlugins as GHC hiding (fst3, (<>))
import qualified Language.Haskell.LSP.Types.Capabilities as LSP
import qualified Data.Text as T
import Development.IDE.Types.Diagnostics
import Control.DeepSeq (NFData(..))
import Data.Aeson
import GHC.Generics
data IdeGhcSession = IdeGhcSession
{ IdeGhcSession -> FilePath -> IO (IdeResult HscEnvEq, [FilePath])
loadSessionFun :: FilePath -> IO (IdeResult HscEnvEq, [FilePath])
, IdeGhcSession -> Int
sessionVersion :: !Int
}
instance Show IdeGhcSession where show :: IdeGhcSession -> FilePath
show IdeGhcSession
_ = FilePath
"IdeGhcSession"
instance NFData IdeGhcSession where rnf :: IdeGhcSession -> ()
rnf !IdeGhcSession
_ = ()
data IdeOptions = IdeOptions
{ IdeOptions -> ParsedSource -> IdePreprocessedSource
optPreprocessor :: GHC.ParsedSource -> IdePreprocessedSource
, IdeOptions -> Action IdeGhcSession
optGhcSession :: Action IdeGhcSession
, IdeOptions -> IdePkgLocationOptions
optPkgLocationOpts :: IdePkgLocationOptions
, IdeOptions -> [FilePath]
optExtensions :: [String]
, IdeOptions -> Int
optThreads :: Int
, IdeOptions -> Maybe FilePath
optShakeFiles :: Maybe FilePath
, IdeOptions -> Maybe FilePath
optShakeProfiling :: Maybe FilePath
, IdeOptions -> IdeOTMemoryProfiling
optOTMemoryProfiling :: IdeOTMemoryProfiling
, IdeOptions -> IdeTesting
optTesting :: IdeTesting
, IdeOptions -> IdeReportProgress
optReportProgress :: IdeReportProgress
, IdeOptions -> FilePath
optLanguageSyntax :: String
, IdeOptions -> Bool
optNewColonConvention :: Bool
, IdeOptions -> [Text]
optKeywords :: [T.Text]
, IdeOptions -> IdeDefer
optDefer :: IdeDefer
, IdeOptions -> CheckProject
optCheckProject :: CheckProject
, IdeOptions -> CheckParents
optCheckParents :: CheckParents
, IdeOptions -> OptHaddockParse
optHaddockParse :: OptHaddockParse
, IdeOptions -> DynFlags -> DynFlags
optCustomDynFlags :: DynFlags -> DynFlags
}
data OptHaddockParse = HaddockParse | NoHaddockParse
deriving (OptHaddockParse -> OptHaddockParse -> Bool
(OptHaddockParse -> OptHaddockParse -> Bool)
-> (OptHaddockParse -> OptHaddockParse -> Bool)
-> Eq OptHaddockParse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OptHaddockParse -> OptHaddockParse -> Bool
$c/= :: OptHaddockParse -> OptHaddockParse -> Bool
== :: OptHaddockParse -> OptHaddockParse -> Bool
$c== :: OptHaddockParse -> OptHaddockParse -> Bool
Eq,Eq OptHaddockParse
Eq OptHaddockParse
-> (OptHaddockParse -> OptHaddockParse -> Ordering)
-> (OptHaddockParse -> OptHaddockParse -> Bool)
-> (OptHaddockParse -> OptHaddockParse -> Bool)
-> (OptHaddockParse -> OptHaddockParse -> Bool)
-> (OptHaddockParse -> OptHaddockParse -> Bool)
-> (OptHaddockParse -> OptHaddockParse -> OptHaddockParse)
-> (OptHaddockParse -> OptHaddockParse -> OptHaddockParse)
-> Ord OptHaddockParse
OptHaddockParse -> OptHaddockParse -> Bool
OptHaddockParse -> OptHaddockParse -> Ordering
OptHaddockParse -> OptHaddockParse -> OptHaddockParse
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: OptHaddockParse -> OptHaddockParse -> OptHaddockParse
$cmin :: OptHaddockParse -> OptHaddockParse -> OptHaddockParse
max :: OptHaddockParse -> OptHaddockParse -> OptHaddockParse
$cmax :: OptHaddockParse -> OptHaddockParse -> OptHaddockParse
>= :: OptHaddockParse -> OptHaddockParse -> Bool
$c>= :: OptHaddockParse -> OptHaddockParse -> Bool
> :: OptHaddockParse -> OptHaddockParse -> Bool
$c> :: OptHaddockParse -> OptHaddockParse -> Bool
<= :: OptHaddockParse -> OptHaddockParse -> Bool
$c<= :: OptHaddockParse -> OptHaddockParse -> Bool
< :: OptHaddockParse -> OptHaddockParse -> Bool
$c< :: OptHaddockParse -> OptHaddockParse -> Bool
compare :: OptHaddockParse -> OptHaddockParse -> Ordering
$ccompare :: OptHaddockParse -> OptHaddockParse -> Ordering
$cp1Ord :: Eq OptHaddockParse
Ord,Int -> OptHaddockParse -> ShowS
[OptHaddockParse] -> ShowS
OptHaddockParse -> FilePath
(Int -> OptHaddockParse -> ShowS)
-> (OptHaddockParse -> FilePath)
-> ([OptHaddockParse] -> ShowS)
-> Show OptHaddockParse
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [OptHaddockParse] -> ShowS
$cshowList :: [OptHaddockParse] -> ShowS
show :: OptHaddockParse -> FilePath
$cshow :: OptHaddockParse -> FilePath
showsPrec :: Int -> OptHaddockParse -> ShowS
$cshowsPrec :: Int -> OptHaddockParse -> ShowS
Show,Int -> OptHaddockParse
OptHaddockParse -> Int
OptHaddockParse -> [OptHaddockParse]
OptHaddockParse -> OptHaddockParse
OptHaddockParse -> OptHaddockParse -> [OptHaddockParse]
OptHaddockParse
-> OptHaddockParse -> OptHaddockParse -> [OptHaddockParse]
(OptHaddockParse -> OptHaddockParse)
-> (OptHaddockParse -> OptHaddockParse)
-> (Int -> OptHaddockParse)
-> (OptHaddockParse -> Int)
-> (OptHaddockParse -> [OptHaddockParse])
-> (OptHaddockParse -> OptHaddockParse -> [OptHaddockParse])
-> (OptHaddockParse -> OptHaddockParse -> [OptHaddockParse])
-> (OptHaddockParse
-> OptHaddockParse -> OptHaddockParse -> [OptHaddockParse])
-> Enum OptHaddockParse
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: OptHaddockParse
-> OptHaddockParse -> OptHaddockParse -> [OptHaddockParse]
$cenumFromThenTo :: OptHaddockParse
-> OptHaddockParse -> OptHaddockParse -> [OptHaddockParse]
enumFromTo :: OptHaddockParse -> OptHaddockParse -> [OptHaddockParse]
$cenumFromTo :: OptHaddockParse -> OptHaddockParse -> [OptHaddockParse]
enumFromThen :: OptHaddockParse -> OptHaddockParse -> [OptHaddockParse]
$cenumFromThen :: OptHaddockParse -> OptHaddockParse -> [OptHaddockParse]
enumFrom :: OptHaddockParse -> [OptHaddockParse]
$cenumFrom :: OptHaddockParse -> [OptHaddockParse]
fromEnum :: OptHaddockParse -> Int
$cfromEnum :: OptHaddockParse -> Int
toEnum :: Int -> OptHaddockParse
$ctoEnum :: Int -> OptHaddockParse
pred :: OptHaddockParse -> OptHaddockParse
$cpred :: OptHaddockParse -> OptHaddockParse
succ :: OptHaddockParse -> OptHaddockParse
$csucc :: OptHaddockParse -> OptHaddockParse
Enum)
newtype CheckProject = CheckProject { CheckProject -> Bool
shouldCheckProject :: Bool }
deriving stock (CheckProject -> CheckProject -> Bool
(CheckProject -> CheckProject -> Bool)
-> (CheckProject -> CheckProject -> Bool) -> Eq CheckProject
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckProject -> CheckProject -> Bool
$c/= :: CheckProject -> CheckProject -> Bool
== :: CheckProject -> CheckProject -> Bool
$c== :: CheckProject -> CheckProject -> Bool
Eq, Eq CheckProject
Eq CheckProject
-> (CheckProject -> CheckProject -> Ordering)
-> (CheckProject -> CheckProject -> Bool)
-> (CheckProject -> CheckProject -> Bool)
-> (CheckProject -> CheckProject -> Bool)
-> (CheckProject -> CheckProject -> Bool)
-> (CheckProject -> CheckProject -> CheckProject)
-> (CheckProject -> CheckProject -> CheckProject)
-> Ord CheckProject
CheckProject -> CheckProject -> Bool
CheckProject -> CheckProject -> Ordering
CheckProject -> CheckProject -> CheckProject
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CheckProject -> CheckProject -> CheckProject
$cmin :: CheckProject -> CheckProject -> CheckProject
max :: CheckProject -> CheckProject -> CheckProject
$cmax :: CheckProject -> CheckProject -> CheckProject
>= :: CheckProject -> CheckProject -> Bool
$c>= :: CheckProject -> CheckProject -> Bool
> :: CheckProject -> CheckProject -> Bool
$c> :: CheckProject -> CheckProject -> Bool
<= :: CheckProject -> CheckProject -> Bool
$c<= :: CheckProject -> CheckProject -> Bool
< :: CheckProject -> CheckProject -> Bool
$c< :: CheckProject -> CheckProject -> Bool
compare :: CheckProject -> CheckProject -> Ordering
$ccompare :: CheckProject -> CheckProject -> Ordering
$cp1Ord :: Eq CheckProject
Ord, Int -> CheckProject -> ShowS
[CheckProject] -> ShowS
CheckProject -> FilePath
(Int -> CheckProject -> ShowS)
-> (CheckProject -> FilePath)
-> ([CheckProject] -> ShowS)
-> Show CheckProject
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [CheckProject] -> ShowS
$cshowList :: [CheckProject] -> ShowS
show :: CheckProject -> FilePath
$cshow :: CheckProject -> FilePath
showsPrec :: Int -> CheckProject -> ShowS
$cshowsPrec :: Int -> CheckProject -> ShowS
Show)
deriving newtype (Value -> Parser [CheckProject]
Value -> Parser CheckProject
(Value -> Parser CheckProject)
-> (Value -> Parser [CheckProject]) -> FromJSON CheckProject
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CheckProject]
$cparseJSONList :: Value -> Parser [CheckProject]
parseJSON :: Value -> Parser CheckProject
$cparseJSON :: Value -> Parser CheckProject
FromJSON,[CheckProject] -> Encoding
[CheckProject] -> Value
CheckProject -> Encoding
CheckProject -> Value
(CheckProject -> Value)
-> (CheckProject -> Encoding)
-> ([CheckProject] -> Value)
-> ([CheckProject] -> Encoding)
-> ToJSON CheckProject
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CheckProject] -> Encoding
$ctoEncodingList :: [CheckProject] -> Encoding
toJSONList :: [CheckProject] -> Value
$ctoJSONList :: [CheckProject] -> Value
toEncoding :: CheckProject -> Encoding
$ctoEncoding :: CheckProject -> Encoding
toJSON :: CheckProject -> Value
$ctoJSON :: CheckProject -> Value
ToJSON)
data CheckParents
= NeverCheck
| CheckOnClose
| CheckOnSaveAndClose
| AlwaysCheck
deriving stock (CheckParents -> CheckParents -> Bool
(CheckParents -> CheckParents -> Bool)
-> (CheckParents -> CheckParents -> Bool) -> Eq CheckParents
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckParents -> CheckParents -> Bool
$c/= :: CheckParents -> CheckParents -> Bool
== :: CheckParents -> CheckParents -> Bool
$c== :: CheckParents -> CheckParents -> Bool
Eq, Eq CheckParents
Eq CheckParents
-> (CheckParents -> CheckParents -> Ordering)
-> (CheckParents -> CheckParents -> Bool)
-> (CheckParents -> CheckParents -> Bool)
-> (CheckParents -> CheckParents -> Bool)
-> (CheckParents -> CheckParents -> Bool)
-> (CheckParents -> CheckParents -> CheckParents)
-> (CheckParents -> CheckParents -> CheckParents)
-> Ord CheckParents
CheckParents -> CheckParents -> Bool
CheckParents -> CheckParents -> Ordering
CheckParents -> CheckParents -> CheckParents
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CheckParents -> CheckParents -> CheckParents
$cmin :: CheckParents -> CheckParents -> CheckParents
max :: CheckParents -> CheckParents -> CheckParents
$cmax :: CheckParents -> CheckParents -> CheckParents
>= :: CheckParents -> CheckParents -> Bool
$c>= :: CheckParents -> CheckParents -> Bool
> :: CheckParents -> CheckParents -> Bool
$c> :: CheckParents -> CheckParents -> Bool
<= :: CheckParents -> CheckParents -> Bool
$c<= :: CheckParents -> CheckParents -> Bool
< :: CheckParents -> CheckParents -> Bool
$c< :: CheckParents -> CheckParents -> Bool
compare :: CheckParents -> CheckParents -> Ordering
$ccompare :: CheckParents -> CheckParents -> Ordering
$cp1Ord :: Eq CheckParents
Ord, Int -> CheckParents -> ShowS
[CheckParents] -> ShowS
CheckParents -> FilePath
(Int -> CheckParents -> ShowS)
-> (CheckParents -> FilePath)
-> ([CheckParents] -> ShowS)
-> Show CheckParents
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [CheckParents] -> ShowS
$cshowList :: [CheckParents] -> ShowS
show :: CheckParents -> FilePath
$cshow :: CheckParents -> FilePath
showsPrec :: Int -> CheckParents -> ShowS
$cshowsPrec :: Int -> CheckParents -> ShowS
Show, (forall x. CheckParents -> Rep CheckParents x)
-> (forall x. Rep CheckParents x -> CheckParents)
-> Generic CheckParents
forall x. Rep CheckParents x -> CheckParents
forall x. CheckParents -> Rep CheckParents x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CheckParents x -> CheckParents
$cfrom :: forall x. CheckParents -> Rep CheckParents x
Generic)
deriving anyclass (Value -> Parser [CheckParents]
Value -> Parser CheckParents
(Value -> Parser CheckParents)
-> (Value -> Parser [CheckParents]) -> FromJSON CheckParents
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CheckParents]
$cparseJSONList :: Value -> Parser [CheckParents]
parseJSON :: Value -> Parser CheckParents
$cparseJSON :: Value -> Parser CheckParents
FromJSON, [CheckParents] -> Encoding
[CheckParents] -> Value
CheckParents -> Encoding
CheckParents -> Value
(CheckParents -> Value)
-> (CheckParents -> Encoding)
-> ([CheckParents] -> Value)
-> ([CheckParents] -> Encoding)
-> ToJSON CheckParents
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CheckParents] -> Encoding
$ctoEncodingList :: [CheckParents] -> Encoding
toJSONList :: [CheckParents] -> Value
$ctoJSONList :: [CheckParents] -> Value
toEncoding :: CheckParents -> Encoding
$ctoEncoding :: CheckParents -> Encoding
toJSON :: CheckParents -> Value
$ctoJSON :: CheckParents -> Value
ToJSON)
data LspConfig
= LspConfig
{ LspConfig -> CheckParents
checkParents :: CheckParents
, LspConfig -> CheckProject
checkProject :: CheckProject
} deriving stock (LspConfig -> LspConfig -> Bool
(LspConfig -> LspConfig -> Bool)
-> (LspConfig -> LspConfig -> Bool) -> Eq LspConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LspConfig -> LspConfig -> Bool
$c/= :: LspConfig -> LspConfig -> Bool
== :: LspConfig -> LspConfig -> Bool
$c== :: LspConfig -> LspConfig -> Bool
Eq, Eq LspConfig
Eq LspConfig
-> (LspConfig -> LspConfig -> Ordering)
-> (LspConfig -> LspConfig -> Bool)
-> (LspConfig -> LspConfig -> Bool)
-> (LspConfig -> LspConfig -> Bool)
-> (LspConfig -> LspConfig -> Bool)
-> (LspConfig -> LspConfig -> LspConfig)
-> (LspConfig -> LspConfig -> LspConfig)
-> Ord LspConfig
LspConfig -> LspConfig -> Bool
LspConfig -> LspConfig -> Ordering
LspConfig -> LspConfig -> LspConfig
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LspConfig -> LspConfig -> LspConfig
$cmin :: LspConfig -> LspConfig -> LspConfig
max :: LspConfig -> LspConfig -> LspConfig
$cmax :: LspConfig -> LspConfig -> LspConfig
>= :: LspConfig -> LspConfig -> Bool
$c>= :: LspConfig -> LspConfig -> Bool
> :: LspConfig -> LspConfig -> Bool
$c> :: LspConfig -> LspConfig -> Bool
<= :: LspConfig -> LspConfig -> Bool
$c<= :: LspConfig -> LspConfig -> Bool
< :: LspConfig -> LspConfig -> Bool
$c< :: LspConfig -> LspConfig -> Bool
compare :: LspConfig -> LspConfig -> Ordering
$ccompare :: LspConfig -> LspConfig -> Ordering
$cp1Ord :: Eq LspConfig
Ord, Int -> LspConfig -> ShowS
[LspConfig] -> ShowS
LspConfig -> FilePath
(Int -> LspConfig -> ShowS)
-> (LspConfig -> FilePath)
-> ([LspConfig] -> ShowS)
-> Show LspConfig
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [LspConfig] -> ShowS
$cshowList :: [LspConfig] -> ShowS
show :: LspConfig -> FilePath
$cshow :: LspConfig -> FilePath
showsPrec :: Int -> LspConfig -> ShowS
$cshowsPrec :: Int -> LspConfig -> ShowS
Show, (forall x. LspConfig -> Rep LspConfig x)
-> (forall x. Rep LspConfig x -> LspConfig) -> Generic LspConfig
forall x. Rep LspConfig x -> LspConfig
forall x. LspConfig -> Rep LspConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LspConfig x -> LspConfig
$cfrom :: forall x. LspConfig -> Rep LspConfig x
Generic)
deriving anyclass (Value -> Parser [LspConfig]
Value -> Parser LspConfig
(Value -> Parser LspConfig)
-> (Value -> Parser [LspConfig]) -> FromJSON LspConfig
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [LspConfig]
$cparseJSONList :: Value -> Parser [LspConfig]
parseJSON :: Value -> Parser LspConfig
$cparseJSON :: Value -> Parser LspConfig
FromJSON, [LspConfig] -> Encoding
[LspConfig] -> Value
LspConfig -> Encoding
LspConfig -> Value
(LspConfig -> Value)
-> (LspConfig -> Encoding)
-> ([LspConfig] -> Value)
-> ([LspConfig] -> Encoding)
-> ToJSON LspConfig
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [LspConfig] -> Encoding
$ctoEncodingList :: [LspConfig] -> Encoding
toJSONList :: [LspConfig] -> Value
$ctoJSONList :: [LspConfig] -> Value
toEncoding :: LspConfig -> Encoding
$ctoEncoding :: LspConfig -> Encoding
toJSON :: LspConfig -> Value
$ctoJSON :: LspConfig -> Value
ToJSON)
defaultLspConfig :: LspConfig
defaultLspConfig :: LspConfig
defaultLspConfig = CheckParents -> CheckProject -> LspConfig
LspConfig CheckParents
CheckOnSaveAndClose (Bool -> CheckProject
CheckProject Bool
True)
data IdePreprocessedSource = IdePreprocessedSource
{ IdePreprocessedSource -> [(SrcSpan, FilePath)]
preprocWarnings :: [(GHC.SrcSpan, String)]
, IdePreprocessedSource -> [(SrcSpan, FilePath)]
preprocErrors :: [(GHC.SrcSpan, String)]
, IdePreprocessedSource -> ParsedSource
preprocSource :: GHC.ParsedSource
}
newtype IdeReportProgress = IdeReportProgress Bool
newtype IdeDefer = IdeDefer Bool
newtype IdeTesting = IdeTesting Bool
newtype IdeOTMemoryProfiling = IdeOTMemoryProfiling Bool
clientSupportsProgress :: LSP.ClientCapabilities -> IdeReportProgress
clientSupportsProgress :: ClientCapabilities -> IdeReportProgress
clientSupportsProgress ClientCapabilities
caps = Bool -> IdeReportProgress
IdeReportProgress (Bool -> IdeReportProgress) -> Bool -> IdeReportProgress
forall a b. (a -> b) -> a -> b
$ Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
==
(WindowClientCapabilities -> Maybe Bool
LSP._workDoneProgress (WindowClientCapabilities -> Maybe Bool)
-> Maybe WindowClientCapabilities -> Maybe Bool
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ClientCapabilities -> Maybe WindowClientCapabilities
LSP._window (ClientCapabilities
caps :: LSP.ClientCapabilities))
defaultIdeOptions :: Action IdeGhcSession -> IdeOptions
defaultIdeOptions :: Action IdeGhcSession -> IdeOptions
defaultIdeOptions Action IdeGhcSession
session = IdeOptions :: (ParsedSource -> IdePreprocessedSource)
-> Action IdeGhcSession
-> IdePkgLocationOptions
-> [FilePath]
-> Int
-> Maybe FilePath
-> Maybe FilePath
-> IdeOTMemoryProfiling
-> IdeTesting
-> IdeReportProgress
-> FilePath
-> Bool
-> [Text]
-> IdeDefer
-> CheckProject
-> CheckParents
-> OptHaddockParse
-> (DynFlags -> DynFlags)
-> IdeOptions
IdeOptions
{optPreprocessor :: ParsedSource -> IdePreprocessedSource
optPreprocessor = [(SrcSpan, FilePath)]
-> [(SrcSpan, FilePath)] -> ParsedSource -> IdePreprocessedSource
IdePreprocessedSource [] []
,optGhcSession :: Action IdeGhcSession
optGhcSession = Action IdeGhcSession
session
,optExtensions :: [FilePath]
optExtensions = [FilePath
"hs", FilePath
"lhs"]
,optPkgLocationOpts :: IdePkgLocationOptions
optPkgLocationOpts = IdePkgLocationOptions
defaultIdePkgLocationOptions
,optThreads :: Int
optThreads = Int
0
,optShakeFiles :: Maybe FilePath
optShakeFiles = Maybe FilePath
forall a. Maybe a
Nothing
,optShakeProfiling :: Maybe FilePath
optShakeProfiling = Maybe FilePath
forall a. Maybe a
Nothing
,optOTMemoryProfiling :: IdeOTMemoryProfiling
optOTMemoryProfiling = Bool -> IdeOTMemoryProfiling
IdeOTMemoryProfiling Bool
False
,optReportProgress :: IdeReportProgress
optReportProgress = Bool -> IdeReportProgress
IdeReportProgress Bool
False
,optLanguageSyntax :: FilePath
optLanguageSyntax = FilePath
"haskell"
,optNewColonConvention :: Bool
optNewColonConvention = Bool
False
,optKeywords :: [Text]
optKeywords = [Text]
haskellKeywords
,optDefer :: IdeDefer
optDefer = Bool -> IdeDefer
IdeDefer Bool
True
,optTesting :: IdeTesting
optTesting = Bool -> IdeTesting
IdeTesting Bool
False
,optCheckProject :: CheckProject
optCheckProject = LspConfig -> CheckProject
checkProject LspConfig
defaultLspConfig
,optCheckParents :: CheckParents
optCheckParents = LspConfig -> CheckParents
checkParents LspConfig
defaultLspConfig
,optHaddockParse :: OptHaddockParse
optHaddockParse = OptHaddockParse
HaddockParse
,optCustomDynFlags :: DynFlags -> DynFlags
optCustomDynFlags = DynFlags -> DynFlags
forall a. a -> a
id
}
data IdePkgLocationOptions = IdePkgLocationOptions
{ IdePkgLocationOptions
-> PackageConfig -> Module -> IO (Maybe FilePath)
optLocateHieFile :: PackageConfig -> Module -> IO (Maybe FilePath)
, IdePkgLocationOptions
-> PackageConfig -> Module -> IO (Maybe FilePath)
optLocateSrcFile :: PackageConfig -> Module -> IO (Maybe FilePath)
}
defaultIdePkgLocationOptions :: IdePkgLocationOptions
defaultIdePkgLocationOptions :: IdePkgLocationOptions
defaultIdePkgLocationOptions = (PackageConfig -> Module -> IO (Maybe FilePath))
-> (PackageConfig -> Module -> IO (Maybe FilePath))
-> IdePkgLocationOptions
IdePkgLocationOptions PackageConfig -> Module -> IO (Maybe FilePath)
forall (m :: * -> *) p p a. Monad m => p -> p -> m (Maybe a)
f PackageConfig -> Module -> IO (Maybe FilePath)
forall (m :: * -> *) p p a. Monad m => p -> p -> m (Maybe a)
f
where f :: p -> p -> m (Maybe a)
f p
_ p
_ = Maybe a -> m (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing
haskellKeywords :: [T.Text]
haskellKeywords :: [Text]
haskellKeywords =
[ Text
"as"
, Text
"case", Text
"of"
, Text
"class", Text
"instance", Text
"type"
, Text
"data", Text
"family", Text
"newtype"
, Text
"default"
, Text
"deriving"
, Text
"do", Text
"mdo", Text
"proc", Text
"rec"
, Text
"forall"
, Text
"foreign"
, Text
"hiding"
, Text
"if", Text
"then", Text
"else"
, Text
"import", Text
"qualified", Text
"hiding"
, Text
"infix", Text
"infixl", Text
"infixr"
, Text
"let", Text
"in", Text
"where"
, Text
"module"
]