-- Copyright (c) 2019 The DAML Authors. All rights reserved.
-- SPDX-License-Identifier: Apache-2.0

{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleInstances  #-}
{-# LANGUAGE GADTs              #-}
{-# LANGUAGE PatternSynonyms    #-}
{-# LANGUAGE TemplateHaskell    #-}
{-# LANGUAGE TypeFamilies       #-}

-- | A Shake implementation of the compiler service, built
--   using the "Shaker" abstraction layer for in-memory use.
--
module Development.IDE.Core.RuleTypes(
    GhcSessionDeps(.., GhcSessionDeps),
    module Development.IDE.Core.RuleTypes
    ) where

import           Control.DeepSeq
import           Control.Exception                            (assert)
import           Control.Lens
import           Data.Aeson.Types                             (Value)
import           Data.Hashable
import qualified Data.Map                                     as M
import           Data.Time.Clock.POSIX
import           Data.Typeable
import           Development.IDE.GHC.Compat                   hiding
                                                              (HieFileResult)
import           Development.IDE.GHC.Compat.Util
import           Development.IDE.GHC.CoreFile
import           Development.IDE.GHC.Util
import           Development.IDE.Graph
import           Development.IDE.Import.DependencyInformation
import           Development.IDE.Types.HscEnvEq               (HscEnvEq)
import           Development.IDE.Types.KnownTargets
import           GHC.Generics                                 (Generic)

import           Data.ByteString                              (ByteString)
import           Data.Text                                    (Text)
import           Development.IDE.Import.FindImports           (ArtifactsLocation)
import           Development.IDE.Spans.Common
import           Development.IDE.Spans.LocalBindings
import           Development.IDE.Types.Diagnostics
import           GHC.Serialized                               (Serialized)
import           Language.LSP.Types                           (Int32,
                                                               NormalizedFilePath)

data LinkableType = ObjectLinkable | BCOLinkable
  deriving (LinkableType -> LinkableType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LinkableType -> LinkableType -> Bool
$c/= :: LinkableType -> LinkableType -> Bool
== :: LinkableType -> LinkableType -> Bool
$c== :: LinkableType -> LinkableType -> Bool
Eq,Eq LinkableType
LinkableType -> LinkableType -> Bool
LinkableType -> LinkableType -> Ordering
LinkableType -> LinkableType -> LinkableType
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 :: LinkableType -> LinkableType -> LinkableType
$cmin :: LinkableType -> LinkableType -> LinkableType
max :: LinkableType -> LinkableType -> LinkableType
$cmax :: LinkableType -> LinkableType -> LinkableType
>= :: LinkableType -> LinkableType -> Bool
$c>= :: LinkableType -> LinkableType -> Bool
> :: LinkableType -> LinkableType -> Bool
$c> :: LinkableType -> LinkableType -> Bool
<= :: LinkableType -> LinkableType -> Bool
$c<= :: LinkableType -> LinkableType -> Bool
< :: LinkableType -> LinkableType -> Bool
$c< :: LinkableType -> LinkableType -> Bool
compare :: LinkableType -> LinkableType -> Ordering
$ccompare :: LinkableType -> LinkableType -> Ordering
Ord,Int -> LinkableType -> ShowS
[LinkableType] -> ShowS
LinkableType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LinkableType] -> ShowS
$cshowList :: [LinkableType] -> ShowS
show :: LinkableType -> String
$cshow :: LinkableType -> String
showsPrec :: Int -> LinkableType -> ShowS
$cshowsPrec :: Int -> LinkableType -> ShowS
Show, forall x. Rep LinkableType x -> LinkableType
forall x. LinkableType -> Rep LinkableType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LinkableType x -> LinkableType
$cfrom :: forall x. LinkableType -> Rep LinkableType x
Generic)
instance Hashable LinkableType
instance NFData   LinkableType

-- | Encode the linkable into an ordered bytestring.
--   This is used to drive an ordered "newness" predicate in the
--   'NeedsCompilation' build rule.
encodeLinkableType :: Maybe LinkableType -> ByteString
encodeLinkableType :: Maybe LinkableType -> ByteString
encodeLinkableType Maybe LinkableType
Nothing               = ByteString
"0"
encodeLinkableType (Just LinkableType
BCOLinkable)    = ByteString
"1"
encodeLinkableType (Just LinkableType
ObjectLinkable) = ByteString
"2"

-- NOTATION
--   Foo+ means Foo for the dependencies
--   Foo* means Foo for me and Foo+

-- | The parse tree for the file using GetFileContents
type instance RuleResult GetParsedModule = ParsedModule

-- | The parse tree for the file using GetFileContents,
-- all comments included using Opt_KeepRawTokenStream
type instance RuleResult GetParsedModuleWithComments = ParsedModule

-- | The dependency information produced by following the imports recursively.
-- This rule will succeed even if there is an error, e.g., a module could not be located,
-- a module could not be parsed or an import cycle.
type instance RuleResult GetDependencyInformation = DependencyInformation

type instance RuleResult GetModuleGraph = DependencyInformation

data GetKnownTargets = GetKnownTargets
  deriving (Int -> GetKnownTargets -> ShowS
[GetKnownTargets] -> ShowS
GetKnownTargets -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetKnownTargets] -> ShowS
$cshowList :: [GetKnownTargets] -> ShowS
show :: GetKnownTargets -> String
$cshow :: GetKnownTargets -> String
showsPrec :: Int -> GetKnownTargets -> ShowS
$cshowsPrec :: Int -> GetKnownTargets -> ShowS
Show, forall x. Rep GetKnownTargets x -> GetKnownTargets
forall x. GetKnownTargets -> Rep GetKnownTargets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetKnownTargets x -> GetKnownTargets
$cfrom :: forall x. GetKnownTargets -> Rep GetKnownTargets x
Generic, GetKnownTargets -> GetKnownTargets -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetKnownTargets -> GetKnownTargets -> Bool
$c/= :: GetKnownTargets -> GetKnownTargets -> Bool
== :: GetKnownTargets -> GetKnownTargets -> Bool
$c== :: GetKnownTargets -> GetKnownTargets -> Bool
Eq, Eq GetKnownTargets
GetKnownTargets -> GetKnownTargets -> Bool
GetKnownTargets -> GetKnownTargets -> Ordering
GetKnownTargets -> GetKnownTargets -> GetKnownTargets
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 :: GetKnownTargets -> GetKnownTargets -> GetKnownTargets
$cmin :: GetKnownTargets -> GetKnownTargets -> GetKnownTargets
max :: GetKnownTargets -> GetKnownTargets -> GetKnownTargets
$cmax :: GetKnownTargets -> GetKnownTargets -> GetKnownTargets
>= :: GetKnownTargets -> GetKnownTargets -> Bool
$c>= :: GetKnownTargets -> GetKnownTargets -> Bool
> :: GetKnownTargets -> GetKnownTargets -> Bool
$c> :: GetKnownTargets -> GetKnownTargets -> Bool
<= :: GetKnownTargets -> GetKnownTargets -> Bool
$c<= :: GetKnownTargets -> GetKnownTargets -> Bool
< :: GetKnownTargets -> GetKnownTargets -> Bool
$c< :: GetKnownTargets -> GetKnownTargets -> Bool
compare :: GetKnownTargets -> GetKnownTargets -> Ordering
$ccompare :: GetKnownTargets -> GetKnownTargets -> Ordering
Ord)
instance Hashable GetKnownTargets
instance NFData   GetKnownTargets
type instance RuleResult GetKnownTargets = KnownTargets

-- | Convert to Core, requires TypeCheck*
type instance RuleResult GenerateCore = ModGuts

data GenerateCore = GenerateCore
    deriving (GenerateCore -> GenerateCore -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GenerateCore -> GenerateCore -> Bool
$c/= :: GenerateCore -> GenerateCore -> Bool
== :: GenerateCore -> GenerateCore -> Bool
$c== :: GenerateCore -> GenerateCore -> Bool
Eq, Int -> GenerateCore -> ShowS
[GenerateCore] -> ShowS
GenerateCore -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GenerateCore] -> ShowS
$cshowList :: [GenerateCore] -> ShowS
show :: GenerateCore -> String
$cshow :: GenerateCore -> String
showsPrec :: Int -> GenerateCore -> ShowS
$cshowsPrec :: Int -> GenerateCore -> ShowS
Show, Typeable, forall x. Rep GenerateCore x -> GenerateCore
forall x. GenerateCore -> Rep GenerateCore x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GenerateCore x -> GenerateCore
$cfrom :: forall x. GenerateCore -> Rep GenerateCore x
Generic)
instance Hashable GenerateCore
instance NFData   GenerateCore

type instance RuleResult GetLinkable = LinkableResult

data LinkableResult
  = LinkableResult
  { LinkableResult -> HomeModInfo
linkableHomeMod :: !HomeModInfo
  , LinkableResult -> ByteString
linkableHash    :: !ByteString
  -- ^ The hash of the core file
  }

instance Show LinkableResult where
    show :: LinkableResult -> String
show = forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module forall b c a. (b -> c) -> (a -> b) -> a -> c
. HomeModInfo -> ModIface_ 'ModIfaceFinal
hm_iface forall b c a. (b -> c) -> (a -> b) -> a -> c
. LinkableResult -> HomeModInfo
linkableHomeMod

instance NFData LinkableResult where
    rnf :: LinkableResult -> ()
rnf = forall a. a -> ()
rwhnf

data GetLinkable = GetLinkable
    deriving (GetLinkable -> GetLinkable -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLinkable -> GetLinkable -> Bool
$c/= :: GetLinkable -> GetLinkable -> Bool
== :: GetLinkable -> GetLinkable -> Bool
$c== :: GetLinkable -> GetLinkable -> Bool
Eq, Int -> GetLinkable -> ShowS
[GetLinkable] -> ShowS
GetLinkable -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLinkable] -> ShowS
$cshowList :: [GetLinkable] -> ShowS
show :: GetLinkable -> String
$cshow :: GetLinkable -> String
showsPrec :: Int -> GetLinkable -> ShowS
$cshowsPrec :: Int -> GetLinkable -> ShowS
Show, Typeable, forall x. Rep GetLinkable x -> GetLinkable
forall x. GetLinkable -> Rep GetLinkable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetLinkable x -> GetLinkable
$cfrom :: forall x. GetLinkable -> Rep GetLinkable x
Generic)
instance Hashable GetLinkable
instance NFData   GetLinkable

data GetImportMap = GetImportMap
    deriving (GetImportMap -> GetImportMap -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetImportMap -> GetImportMap -> Bool
$c/= :: GetImportMap -> GetImportMap -> Bool
== :: GetImportMap -> GetImportMap -> Bool
$c== :: GetImportMap -> GetImportMap -> Bool
Eq, Int -> GetImportMap -> ShowS
[GetImportMap] -> ShowS
GetImportMap -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetImportMap] -> ShowS
$cshowList :: [GetImportMap] -> ShowS
show :: GetImportMap -> String
$cshow :: GetImportMap -> String
showsPrec :: Int -> GetImportMap -> ShowS
$cshowsPrec :: Int -> GetImportMap -> ShowS
Show, Typeable, forall x. Rep GetImportMap x -> GetImportMap
forall x. GetImportMap -> Rep GetImportMap x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetImportMap x -> GetImportMap
$cfrom :: forall x. GetImportMap -> Rep GetImportMap x
Generic)
instance Hashable GetImportMap
instance NFData   GetImportMap

type instance RuleResult GetImportMap = ImportMap
newtype ImportMap = ImportMap
  { ImportMap -> Map ModuleName NormalizedFilePath
importMap :: M.Map ModuleName NormalizedFilePath -- ^ Where are the modules imported by this file located?
  } deriving stock Int -> ImportMap -> ShowS
[ImportMap] -> ShowS
ImportMap -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImportMap] -> ShowS
$cshowList :: [ImportMap] -> ShowS
show :: ImportMap -> String
$cshow :: ImportMap -> String
showsPrec :: Int -> ImportMap -> ShowS
$cshowsPrec :: Int -> ImportMap -> ShowS
Show
    deriving newtype ImportMap -> ()
forall a. (a -> ()) -> NFData a
rnf :: ImportMap -> ()
$crnf :: ImportMap -> ()
NFData

data Splices = Splices
    { Splices -> [(LHsExpr GhcTc, LHsExpr GhcPs)]
exprSplices :: [(LHsExpr GhcTc, LHsExpr GhcPs)]
    , Splices -> [(LHsExpr GhcTc, LPat GhcPs)]
patSplices  :: [(LHsExpr GhcTc, LPat GhcPs)]
    , Splices -> [(LHsExpr GhcTc, LHsType GhcPs)]
typeSplices :: [(LHsExpr GhcTc, LHsType GhcPs)]
    , Splices -> [(LHsExpr GhcTc, [LHsDecl GhcPs])]
declSplices :: [(LHsExpr GhcTc, [LHsDecl GhcPs])]
    , Splices -> [(LHsExpr GhcTc, Serialized)]
awSplices   :: [(LHsExpr GhcTc, Serialized)]
    }

instance Semigroup Splices where
    Splices [(LHsExpr GhcTc, LHsExpr GhcPs)]
e [(LHsExpr GhcTc, LPat GhcPs)]
p [(LHsExpr GhcTc, LHsType GhcPs)]
t [(LHsExpr GhcTc, [LHsDecl GhcPs])]
d [(LHsExpr GhcTc, Serialized)]
aw <> :: Splices -> Splices -> Splices
<> Splices [(LHsExpr GhcTc, LHsExpr GhcPs)]
e' [(LHsExpr GhcTc, LPat GhcPs)]
p' [(LHsExpr GhcTc, LHsType GhcPs)]
t' [(LHsExpr GhcTc, [LHsDecl GhcPs])]
d' [(LHsExpr GhcTc, Serialized)]
aw' =
        [(LHsExpr GhcTc, LHsExpr GhcPs)]
-> [(LHsExpr GhcTc, LPat GhcPs)]
-> [(LHsExpr GhcTc, LHsType GhcPs)]
-> [(LHsExpr GhcTc, [LHsDecl GhcPs])]
-> [(LHsExpr GhcTc, Serialized)]
-> Splices
Splices
            ([(LHsExpr GhcTc, LHsExpr GhcPs)]
e forall a. Semigroup a => a -> a -> a
<> [(LHsExpr GhcTc, LHsExpr GhcPs)]
e')
            ([(LHsExpr GhcTc, LPat GhcPs)]
p forall a. Semigroup a => a -> a -> a
<> [(LHsExpr GhcTc, LPat GhcPs)]
p')
            ([(LHsExpr GhcTc, LHsType GhcPs)]
t forall a. Semigroup a => a -> a -> a
<> [(LHsExpr GhcTc, LHsType GhcPs)]
t')
            ([(LHsExpr GhcTc, [LHsDecl GhcPs])]
d forall a. Semigroup a => a -> a -> a
<> [(LHsExpr GhcTc, [LHsDecl GhcPs])]
d')
            ([(LHsExpr GhcTc, Serialized)]
aw forall a. Semigroup a => a -> a -> a
<> [(LHsExpr GhcTc, Serialized)]
aw')

instance Monoid Splices where
    mempty :: Splices
mempty = [(LHsExpr GhcTc, LHsExpr GhcPs)]
-> [(LHsExpr GhcTc, LPat GhcPs)]
-> [(LHsExpr GhcTc, LHsType GhcPs)]
-> [(LHsExpr GhcTc, [LHsDecl GhcPs])]
-> [(LHsExpr GhcTc, Serialized)]
-> Splices
Splices forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty

instance NFData Splices where
    rnf :: Splices -> ()
rnf Splices {[(LHsExpr GhcTc, [LHsDecl GhcPs])]
[(LHsExpr GhcTc, Serialized)]
[(LHsExpr GhcTc, LHsType GhcPs)]
[(LHsExpr GhcTc, LPat GhcPs)]
[(LHsExpr GhcTc, LHsExpr GhcPs)]
awSplices :: [(LHsExpr GhcTc, Serialized)]
declSplices :: [(LHsExpr GhcTc, [LHsDecl GhcPs])]
typeSplices :: [(LHsExpr GhcTc, LHsType GhcPs)]
patSplices :: [(LHsExpr GhcTc, LPat GhcPs)]
exprSplices :: [(LHsExpr GhcTc, LHsExpr GhcPs)]
awSplices :: Splices -> [(LHsExpr GhcTc, Serialized)]
declSplices :: Splices -> [(LHsExpr GhcTc, [LHsDecl GhcPs])]
typeSplices :: Splices -> [(LHsExpr GhcTc, LHsType GhcPs)]
patSplices :: Splices -> [(LHsExpr GhcTc, LPat GhcPs)]
exprSplices :: Splices -> [(LHsExpr GhcTc, LHsExpr GhcPs)]
..} =
        forall (f :: * -> *) a. NFData1 f => (a -> ()) -> f a -> ()
liftRnf forall a. a -> ()
rwhnf [(LHsExpr GhcTc, LHsExpr GhcPs)]
exprSplices seq :: forall a b. a -> b -> b
`seq`
        forall (f :: * -> *) a. NFData1 f => (a -> ()) -> f a -> ()
liftRnf forall a. a -> ()
rwhnf [(LHsExpr GhcTc, LPat GhcPs)]
patSplices seq :: forall a b. a -> b -> b
`seq`
        forall (f :: * -> *) a. NFData1 f => (a -> ()) -> f a -> ()
liftRnf forall a. a -> ()
rwhnf [(LHsExpr GhcTc, LHsType GhcPs)]
typeSplices seq :: forall a b. a -> b -> b
`seq` forall (f :: * -> *) a. NFData1 f => (a -> ()) -> f a -> ()
liftRnf forall a. a -> ()
rwhnf [(LHsExpr GhcTc, [LHsDecl GhcPs])]
declSplices seq :: forall a b. a -> b -> b
`seq` ()

-- | Contains the typechecked module and the OrigNameCache entry for
-- that module.
data TcModuleResult = TcModuleResult
    { TcModuleResult -> ParsedModule
tmrParsed          :: ParsedModule
    , TcModuleResult -> RenamedSource
tmrRenamed         :: RenamedSource
    , TcModuleResult -> TcGblEnv
tmrTypechecked     :: TcGblEnv
    , TcModuleResult -> Splices
tmrTopLevelSplices :: Splices
    -- ^ Typechecked splice information
    , TcModuleResult -> Bool
tmrDeferredError   :: !Bool
    -- ^ Did we defer any type errors for this module?
    , TcModuleResult -> ModuleEnv ByteString
tmrRuntimeModules  :: !(ModuleEnv ByteString)
        -- ^ Which modules did we need at runtime while compiling this file?
        -- Used for recompilation checking in the presence of TH
        -- Stores the hash of their core file
    }
instance Show TcModuleResult where
    show :: TcModuleResult -> String
show = forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParsedModule -> ModSummary
pm_mod_summary forall b c a. (b -> c) -> (a -> b) -> a -> c
. TcModuleResult -> ParsedModule
tmrParsed

instance NFData TcModuleResult where
    rnf :: TcModuleResult -> ()
rnf = forall a. a -> ()
rwhnf

tmrModSummary :: TcModuleResult -> ModSummary
tmrModSummary :: TcModuleResult -> ModSummary
tmrModSummary = ParsedModule -> ModSummary
pm_mod_summary forall b c a. (b -> c) -> (a -> b) -> a -> c
. TcModuleResult -> ParsedModule
tmrParsed

data HiFileResult = HiFileResult
    { HiFileResult -> ModSummary
hirModSummary     :: !ModSummary
    -- Bang patterns here are important to stop the result retaining
    -- a reference to a typechecked module
    , HiFileResult -> ModIface_ 'ModIfaceFinal
hirModIface       :: !ModIface
    , HiFileResult -> ModDetails
hirModDetails     :: ModDetails
    -- ^ Populated lazily
    , HiFileResult -> ByteString
hirIfaceFp        :: !ByteString
    -- ^ Fingerprint for the ModIface
    , HiFileResult -> ModuleEnv ByteString
hirRuntimeModules :: !(ModuleEnv ByteString)
    -- ^ same as tmrRuntimeModules
    , HiFileResult -> Maybe (CoreFile, ByteString)
hirCoreFp         :: !(Maybe (CoreFile, ByteString))
    -- ^ If we wrote a core file for this module, then its contents (lazily deserialised)
    -- along with its hash
    }

hiFileFingerPrint :: HiFileResult -> ByteString
hiFileFingerPrint :: HiFileResult -> ByteString
hiFileFingerPrint HiFileResult{Maybe (CoreFile, ByteString)
ByteString
ModIface_ 'ModIfaceFinal
ModSummary
ModDetails
ModuleEnv ByteString
hirCoreFp :: Maybe (CoreFile, ByteString)
hirRuntimeModules :: ModuleEnv ByteString
hirIfaceFp :: ByteString
hirModDetails :: ModDetails
hirModIface :: ModIface_ 'ModIfaceFinal
hirModSummary :: ModSummary
hirCoreFp :: HiFileResult -> Maybe (CoreFile, ByteString)
hirRuntimeModules :: HiFileResult -> ModuleEnv ByteString
hirIfaceFp :: HiFileResult -> ByteString
hirModDetails :: HiFileResult -> ModDetails
hirModIface :: HiFileResult -> ModIface_ 'ModIfaceFinal
hirModSummary :: HiFileResult -> ModSummary
..} = ByteString
hirIfaceFp forall a. Semigroup a => a -> a -> a
<> forall b a. b -> (a -> b) -> Maybe a -> b
maybe ByteString
"" forall a b. (a, b) -> b
snd Maybe (CoreFile, ByteString)
hirCoreFp

mkHiFileResult :: ModSummary -> ModIface -> ModDetails -> ModuleEnv ByteString -> Maybe (CoreFile, ByteString) -> HiFileResult
mkHiFileResult :: ModSummary
-> ModIface_ 'ModIfaceFinal
-> ModDetails
-> ModuleEnv ByteString
-> Maybe (CoreFile, ByteString)
-> HiFileResult
mkHiFileResult ModSummary
hirModSummary ModIface_ 'ModIfaceFinal
hirModIface ModDetails
hirModDetails ModuleEnv ByteString
hirRuntimeModules Maybe (CoreFile, ByteString)
hirCoreFp =
    forall a. (?callStack::CallStack) => Bool -> a -> a
assert (case Maybe (CoreFile, ByteString)
hirCoreFp of Just (CoreFile{Fingerprint
cf_iface_hash :: CoreFile -> Fingerprint
cf_iface_hash :: Fingerprint
cf_iface_hash}, ByteString
_)
                                -> ModIface_ 'ModIfaceFinal -> Fingerprint
getModuleHash ModIface_ 'ModIfaceFinal
hirModIface forall a. Eq a => a -> a -> Bool
== Fingerprint
cf_iface_hash
                              Maybe (CoreFile, ByteString)
_ -> Bool
True)
    HiFileResult{Maybe (CoreFile, ByteString)
ByteString
ModIface_ 'ModIfaceFinal
ModSummary
ModDetails
ModuleEnv ByteString
hirIfaceFp :: ByteString
hirCoreFp :: Maybe (CoreFile, ByteString)
hirRuntimeModules :: ModuleEnv ByteString
hirModDetails :: ModDetails
hirModIface :: ModIface_ 'ModIfaceFinal
hirModSummary :: ModSummary
hirCoreFp :: Maybe (CoreFile, ByteString)
hirRuntimeModules :: ModuleEnv ByteString
hirIfaceFp :: ByteString
hirModDetails :: ModDetails
hirModIface :: ModIface_ 'ModIfaceFinal
hirModSummary :: ModSummary
..}
  where
    hirIfaceFp :: ByteString
hirIfaceFp = Fingerprint -> ByteString
fingerprintToBS forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModIface_ 'ModIfaceFinal -> Fingerprint
getModuleHash forall a b. (a -> b) -> a -> b
$ ModIface_ 'ModIfaceFinal
hirModIface -- will always be two bytes

instance NFData HiFileResult where
    rnf :: HiFileResult -> ()
rnf = forall a. a -> ()
rwhnf

instance Show HiFileResult where
    show :: HiFileResult -> String
show = forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. HiFileResult -> ModSummary
hirModSummary

-- | Save the uncompressed AST here, we compress it just before writing to disk
data HieAstResult
  = forall a . (Typeable a) =>  HAR
  { HieAstResult -> Module
hieModule :: Module
  , ()
hieAst    :: !(HieASTs a)
  , ()
refMap    :: RefMap a
  -- ^ Lazy because its value only depends on the hieAst, which is bundled in this type
  -- Lazyness can't cause leaks here because the lifetime of `refMap` will be the same
  -- as that of `hieAst`
  , HieAstResult -> Map Name [RealSrcSpan]
typeRefs  :: M.Map Name [RealSrcSpan]
  -- ^ type references in this file
  , ()
hieKind   :: !(HieKind a)
  -- ^ Is this hie file loaded from the disk, or freshly computed?
  }

data HieKind a where
  HieFromDisk :: !HieFile -> HieKind TypeIndex
  HieFresh :: HieKind Type

instance NFData (HieKind a) where
    rnf :: HieKind a -> ()
rnf (HieFromDisk HieFile
hf) = forall a. NFData a => a -> ()
rnf HieFile
hf
    rnf HieKind a
HieFresh         = ()

instance NFData HieAstResult where
    rnf :: HieAstResult -> ()
rnf (HAR Module
m HieASTs a
hf RefMap a
_rm Map Name [RealSrcSpan]
_tr HieKind a
kind) = forall a. NFData a => a -> ()
rnf Module
m seq :: forall a b. a -> b -> b
`seq` forall a. a -> ()
rwhnf HieASTs a
hf seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf HieKind a
kind

instance Show HieAstResult where
    show :: HieAstResult -> String
show = forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. HieAstResult -> Module
hieModule

-- | The type checked version of this file, requires TypeCheck+
type instance RuleResult TypeCheck = TcModuleResult

-- | The uncompressed HieAST
type instance RuleResult GetHieAst = HieAstResult

-- | A IntervalMap telling us what is in scope at each point
type instance RuleResult GetBindings = Bindings

data DocAndKindMap = DKMap {DocAndKindMap -> DocMap
getDocMap :: !DocMap, DocAndKindMap -> KindMap
getKindMap :: !KindMap}
instance NFData DocAndKindMap where
    rnf :: DocAndKindMap -> ()
rnf (DKMap DocMap
a KindMap
b) = forall a. a -> ()
rwhnf DocMap
a seq :: forall a b. a -> b -> b
`seq` forall a. a -> ()
rwhnf KindMap
b

instance Show DocAndKindMap where
    show :: DocAndKindMap -> String
show = forall a b. a -> b -> a
const String
"docmap"

type instance RuleResult GetDocMap = DocAndKindMap

-- | A GHC session that we reuse.
type instance RuleResult GhcSession = HscEnvEq

-- | A GHC session preloaded with all the dependencies
-- This rule is also responsible for calling ReportImportCycles for the direct dependencies
type instance RuleResult GhcSessionDeps = HscEnvEq

-- | Resolve the imports in a module to the file path of a module in the same package
type instance RuleResult GetLocatedImports = [(Located ModuleName, Maybe ArtifactsLocation)]

-- | This rule is used to report import cycles. It depends on GetDependencyInformation.
-- We cannot report the cycles directly from GetDependencyInformation since
-- we can only report diagnostics for the current file.
type instance RuleResult ReportImportCycles = ()

-- | Read the module interface file from disk. Throws an error for VFS files.
--   This is an internal rule, use 'GetModIface' instead.
type instance RuleResult GetModIfaceFromDisk = HiFileResult

-- | GetModIfaceFromDisk and index the `.hie` file into the database.
--   This is an internal rule, use 'GetModIface' instead.
type instance RuleResult GetModIfaceFromDiskAndIndex = HiFileResult

-- | Get a module interface details, either from an interface file or a typechecked module
type instance RuleResult GetModIface = HiFileResult

-- | Get the contents of a file, either dirty (if the buffer is modified) or Nothing to mean use from disk.
type instance RuleResult GetFileContents = (FileVersion, Maybe Text)

type instance RuleResult GetFileExists = Bool

type instance RuleResult AddWatchedFile = Bool


-- The Shake key type for getModificationTime queries
newtype GetModificationTime = GetModificationTime_
    { GetModificationTime -> Bool
missingFileDiagnostics :: Bool
      -- ^ If false, missing file diagnostics are not reported
    }
    deriving (forall x. Rep GetModificationTime x -> GetModificationTime
forall x. GetModificationTime -> Rep GetModificationTime x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetModificationTime x -> GetModificationTime
$cfrom :: forall x. GetModificationTime -> Rep GetModificationTime x
Generic)

instance Show GetModificationTime where
    show :: GetModificationTime -> String
show GetModificationTime
_ = String
"GetModificationTime"

instance Eq GetModificationTime where
    -- Since the diagnostics are not part of the answer, the query identity is
    -- independent from the 'missingFileDiagnostics' field
    GetModificationTime
_ == :: GetModificationTime -> GetModificationTime -> Bool
== GetModificationTime
_ = Bool
True

instance Hashable GetModificationTime where
    -- Since the diagnostics are not part of the answer, the query identity is
    -- independent from the 'missingFileDiagnostics' field
    hashWithSalt :: Int -> GetModificationTime -> Int
hashWithSalt Int
salt GetModificationTime
_ = Int
salt

instance NFData   GetModificationTime

pattern GetModificationTime :: GetModificationTime
pattern $bGetModificationTime :: GetModificationTime
$mGetModificationTime :: forall {r}.
GetModificationTime -> ((# #) -> r) -> ((# #) -> r) -> r
GetModificationTime = GetModificationTime_ {missingFileDiagnostics=True}

-- | Get the modification time of a file.
type instance RuleResult GetModificationTime = FileVersion

-- | Either the mtime from disk or an LSP version
--   LSP versions always compare as greater than on disk versions
data FileVersion
    = ModificationTime !POSIXTime -- order of constructors is relevant
    | VFSVersion !Int32
    deriving (Int -> FileVersion -> ShowS
[FileVersion] -> ShowS
FileVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileVersion] -> ShowS
$cshowList :: [FileVersion] -> ShowS
show :: FileVersion -> String
$cshow :: FileVersion -> String
showsPrec :: Int -> FileVersion -> ShowS
$cshowsPrec :: Int -> FileVersion -> ShowS
Show, forall x. Rep FileVersion x -> FileVersion
forall x. FileVersion -> Rep FileVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FileVersion x -> FileVersion
$cfrom :: forall x. FileVersion -> Rep FileVersion x
Generic, FileVersion -> FileVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileVersion -> FileVersion -> Bool
$c/= :: FileVersion -> FileVersion -> Bool
== :: FileVersion -> FileVersion -> Bool
$c== :: FileVersion -> FileVersion -> Bool
Eq, Eq FileVersion
FileVersion -> FileVersion -> Bool
FileVersion -> FileVersion -> Ordering
FileVersion -> FileVersion -> FileVersion
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 :: FileVersion -> FileVersion -> FileVersion
$cmin :: FileVersion -> FileVersion -> FileVersion
max :: FileVersion -> FileVersion -> FileVersion
$cmax :: FileVersion -> FileVersion -> FileVersion
>= :: FileVersion -> FileVersion -> Bool
$c>= :: FileVersion -> FileVersion -> Bool
> :: FileVersion -> FileVersion -> Bool
$c> :: FileVersion -> FileVersion -> Bool
<= :: FileVersion -> FileVersion -> Bool
$c<= :: FileVersion -> FileVersion -> Bool
< :: FileVersion -> FileVersion -> Bool
$c< :: FileVersion -> FileVersion -> Bool
compare :: FileVersion -> FileVersion -> Ordering
$ccompare :: FileVersion -> FileVersion -> Ordering
Ord)

instance NFData FileVersion

vfsVersion :: FileVersion -> Maybe Int32
vfsVersion :: FileVersion -> Maybe Int32
vfsVersion (VFSVersion Int32
i)     = forall a. a -> Maybe a
Just Int32
i
vfsVersion ModificationTime{} = forall a. Maybe a
Nothing

data GetFileContents = GetFileContents
    deriving (GetFileContents -> GetFileContents -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFileContents -> GetFileContents -> Bool
$c/= :: GetFileContents -> GetFileContents -> Bool
== :: GetFileContents -> GetFileContents -> Bool
$c== :: GetFileContents -> GetFileContents -> Bool
Eq, Int -> GetFileContents -> ShowS
[GetFileContents] -> ShowS
GetFileContents -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFileContents] -> ShowS
$cshowList :: [GetFileContents] -> ShowS
show :: GetFileContents -> String
$cshow :: GetFileContents -> String
showsPrec :: Int -> GetFileContents -> ShowS
$cshowsPrec :: Int -> GetFileContents -> ShowS
Show, forall x. Rep GetFileContents x -> GetFileContents
forall x. GetFileContents -> Rep GetFileContents x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFileContents x -> GetFileContents
$cfrom :: forall x. GetFileContents -> Rep GetFileContents x
Generic)
instance Hashable GetFileContents
instance NFData   GetFileContents

data GetFileExists = GetFileExists
    deriving (GetFileExists -> GetFileExists -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFileExists -> GetFileExists -> Bool
$c/= :: GetFileExists -> GetFileExists -> Bool
== :: GetFileExists -> GetFileExists -> Bool
$c== :: GetFileExists -> GetFileExists -> Bool
Eq, Int -> GetFileExists -> ShowS
[GetFileExists] -> ShowS
GetFileExists -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFileExists] -> ShowS
$cshowList :: [GetFileExists] -> ShowS
show :: GetFileExists -> String
$cshow :: GetFileExists -> String
showsPrec :: Int -> GetFileExists -> ShowS
$cshowsPrec :: Int -> GetFileExists -> ShowS
Show, Typeable, forall x. Rep GetFileExists x -> GetFileExists
forall x. GetFileExists -> Rep GetFileExists x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFileExists x -> GetFileExists
$cfrom :: forall x. GetFileExists -> Rep GetFileExists x
Generic)

instance NFData   GetFileExists
instance Hashable GetFileExists

data FileOfInterestStatus
  = OnDisk
  | Modified { FileOfInterestStatus -> Bool
firstOpen :: !Bool -- ^ was this file just opened
             }
  deriving (FileOfInterestStatus -> FileOfInterestStatus -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileOfInterestStatus -> FileOfInterestStatus -> Bool
$c/= :: FileOfInterestStatus -> FileOfInterestStatus -> Bool
== :: FileOfInterestStatus -> FileOfInterestStatus -> Bool
$c== :: FileOfInterestStatus -> FileOfInterestStatus -> Bool
Eq, Int -> FileOfInterestStatus -> ShowS
[FileOfInterestStatus] -> ShowS
FileOfInterestStatus -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileOfInterestStatus] -> ShowS
$cshowList :: [FileOfInterestStatus] -> ShowS
show :: FileOfInterestStatus -> String
$cshow :: FileOfInterestStatus -> String
showsPrec :: Int -> FileOfInterestStatus -> ShowS
$cshowsPrec :: Int -> FileOfInterestStatus -> ShowS
Show, Typeable, forall x. Rep FileOfInterestStatus x -> FileOfInterestStatus
forall x. FileOfInterestStatus -> Rep FileOfInterestStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FileOfInterestStatus x -> FileOfInterestStatus
$cfrom :: forall x. FileOfInterestStatus -> Rep FileOfInterestStatus x
Generic)
instance Hashable FileOfInterestStatus
instance NFData   FileOfInterestStatus

data IsFileOfInterestResult = NotFOI | IsFOI FileOfInterestStatus
  deriving (IsFileOfInterestResult -> IsFileOfInterestResult -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IsFileOfInterestResult -> IsFileOfInterestResult -> Bool
$c/= :: IsFileOfInterestResult -> IsFileOfInterestResult -> Bool
== :: IsFileOfInterestResult -> IsFileOfInterestResult -> Bool
$c== :: IsFileOfInterestResult -> IsFileOfInterestResult -> Bool
Eq, Int -> IsFileOfInterestResult -> ShowS
[IsFileOfInterestResult] -> ShowS
IsFileOfInterestResult -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IsFileOfInterestResult] -> ShowS
$cshowList :: [IsFileOfInterestResult] -> ShowS
show :: IsFileOfInterestResult -> String
$cshow :: IsFileOfInterestResult -> String
showsPrec :: Int -> IsFileOfInterestResult -> ShowS
$cshowsPrec :: Int -> IsFileOfInterestResult -> ShowS
Show, Typeable, forall x. Rep IsFileOfInterestResult x -> IsFileOfInterestResult
forall x. IsFileOfInterestResult -> Rep IsFileOfInterestResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IsFileOfInterestResult x -> IsFileOfInterestResult
$cfrom :: forall x. IsFileOfInterestResult -> Rep IsFileOfInterestResult x
Generic)
instance Hashable IsFileOfInterestResult
instance NFData   IsFileOfInterestResult

type instance RuleResult IsFileOfInterest = IsFileOfInterestResult

data ModSummaryResult = ModSummaryResult
  { ModSummaryResult -> ModSummary
msrModSummary  :: !ModSummary
  , ModSummaryResult -> [LImportDecl GhcPs]
msrImports     :: [LImportDecl GhcPs]
  , ModSummaryResult -> Fingerprint
msrFingerprint :: !Fingerprint
  , ModSummaryResult -> HscEnv
msrHscEnv      :: !HscEnv
  -- ^ HscEnv for this particular ModSummary.
  -- Contains initialised plugins, parsed options, etc...
  --
  -- Implicit assumption: DynFlags in 'msrModSummary' are the same as
  -- the DynFlags in 'msrHscEnv'.
  }

instance Show ModSummaryResult where
    show :: ModSummaryResult -> String
show ModSummaryResult
_ = String
"<ModSummaryResult>"
instance NFData ModSummaryResult where
    rnf :: ModSummaryResult -> ()
rnf ModSummaryResult{[LImportDecl GhcPs]
Fingerprint
HscEnv
ModSummary
msrHscEnv :: HscEnv
msrFingerprint :: Fingerprint
msrImports :: [LImportDecl GhcPs]
msrModSummary :: ModSummary
msrHscEnv :: ModSummaryResult -> HscEnv
msrFingerprint :: ModSummaryResult -> Fingerprint
msrImports :: ModSummaryResult -> [LImportDecl GhcPs]
msrModSummary :: ModSummaryResult -> ModSummary
..} =
        forall a. NFData a => a -> ()
rnf ModSummary
msrModSummary seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf [LImportDecl GhcPs]
msrImports seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf Fingerprint
msrFingerprint

-- | Generate a ModSummary that has enough information to be used to get .hi and .hie files.
-- without needing to parse the entire source
type instance RuleResult GetModSummary = ModSummaryResult

-- | Generate a ModSummary with the timestamps and preprocessed content elided, for more successful early cutoff
type instance RuleResult GetModSummaryWithoutTimestamps = ModSummaryResult

data GetParsedModule = GetParsedModule
    deriving (GetParsedModule -> GetParsedModule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetParsedModule -> GetParsedModule -> Bool
$c/= :: GetParsedModule -> GetParsedModule -> Bool
== :: GetParsedModule -> GetParsedModule -> Bool
$c== :: GetParsedModule -> GetParsedModule -> Bool
Eq, Int -> GetParsedModule -> ShowS
[GetParsedModule] -> ShowS
GetParsedModule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetParsedModule] -> ShowS
$cshowList :: [GetParsedModule] -> ShowS
show :: GetParsedModule -> String
$cshow :: GetParsedModule -> String
showsPrec :: Int -> GetParsedModule -> ShowS
$cshowsPrec :: Int -> GetParsedModule -> ShowS
Show, Typeable, forall x. Rep GetParsedModule x -> GetParsedModule
forall x. GetParsedModule -> Rep GetParsedModule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetParsedModule x -> GetParsedModule
$cfrom :: forall x. GetParsedModule -> Rep GetParsedModule x
Generic)
instance Hashable GetParsedModule
instance NFData   GetParsedModule

data GetParsedModuleWithComments = GetParsedModuleWithComments
    deriving (GetParsedModuleWithComments -> GetParsedModuleWithComments -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetParsedModuleWithComments -> GetParsedModuleWithComments -> Bool
$c/= :: GetParsedModuleWithComments -> GetParsedModuleWithComments -> Bool
== :: GetParsedModuleWithComments -> GetParsedModuleWithComments -> Bool
$c== :: GetParsedModuleWithComments -> GetParsedModuleWithComments -> Bool
Eq, Int -> GetParsedModuleWithComments -> ShowS
[GetParsedModuleWithComments] -> ShowS
GetParsedModuleWithComments -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetParsedModuleWithComments] -> ShowS
$cshowList :: [GetParsedModuleWithComments] -> ShowS
show :: GetParsedModuleWithComments -> String
$cshow :: GetParsedModuleWithComments -> String
showsPrec :: Int -> GetParsedModuleWithComments -> ShowS
$cshowsPrec :: Int -> GetParsedModuleWithComments -> ShowS
Show, Typeable, forall x.
Rep GetParsedModuleWithComments x -> GetParsedModuleWithComments
forall x.
GetParsedModuleWithComments -> Rep GetParsedModuleWithComments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetParsedModuleWithComments x -> GetParsedModuleWithComments
$cfrom :: forall x.
GetParsedModuleWithComments -> Rep GetParsedModuleWithComments x
Generic)
instance Hashable GetParsedModuleWithComments
instance NFData   GetParsedModuleWithComments

data GetLocatedImports = GetLocatedImports
    deriving (GetLocatedImports -> GetLocatedImports -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLocatedImports -> GetLocatedImports -> Bool
$c/= :: GetLocatedImports -> GetLocatedImports -> Bool
== :: GetLocatedImports -> GetLocatedImports -> Bool
$c== :: GetLocatedImports -> GetLocatedImports -> Bool
Eq, Int -> GetLocatedImports -> ShowS
[GetLocatedImports] -> ShowS
GetLocatedImports -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLocatedImports] -> ShowS
$cshowList :: [GetLocatedImports] -> ShowS
show :: GetLocatedImports -> String
$cshow :: GetLocatedImports -> String
showsPrec :: Int -> GetLocatedImports -> ShowS
$cshowsPrec :: Int -> GetLocatedImports -> ShowS
Show, Typeable, forall x. Rep GetLocatedImports x -> GetLocatedImports
forall x. GetLocatedImports -> Rep GetLocatedImports x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetLocatedImports x -> GetLocatedImports
$cfrom :: forall x. GetLocatedImports -> Rep GetLocatedImports x
Generic)
instance Hashable GetLocatedImports
instance NFData   GetLocatedImports

-- | Does this module need to be compiled?
type instance RuleResult NeedsCompilation = Maybe LinkableType

data NeedsCompilation = NeedsCompilation
    deriving (NeedsCompilation -> NeedsCompilation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NeedsCompilation -> NeedsCompilation -> Bool
$c/= :: NeedsCompilation -> NeedsCompilation -> Bool
== :: NeedsCompilation -> NeedsCompilation -> Bool
$c== :: NeedsCompilation -> NeedsCompilation -> Bool
Eq, Int -> NeedsCompilation -> ShowS
[NeedsCompilation] -> ShowS
NeedsCompilation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NeedsCompilation] -> ShowS
$cshowList :: [NeedsCompilation] -> ShowS
show :: NeedsCompilation -> String
$cshow :: NeedsCompilation -> String
showsPrec :: Int -> NeedsCompilation -> ShowS
$cshowsPrec :: Int -> NeedsCompilation -> ShowS
Show, Typeable, forall x. Rep NeedsCompilation x -> NeedsCompilation
forall x. NeedsCompilation -> Rep NeedsCompilation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NeedsCompilation x -> NeedsCompilation
$cfrom :: forall x. NeedsCompilation -> Rep NeedsCompilation x
Generic)
instance Hashable NeedsCompilation
instance NFData   NeedsCompilation

data GetDependencyInformation = GetDependencyInformation
    deriving (GetDependencyInformation -> GetDependencyInformation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDependencyInformation -> GetDependencyInformation -> Bool
$c/= :: GetDependencyInformation -> GetDependencyInformation -> Bool
== :: GetDependencyInformation -> GetDependencyInformation -> Bool
$c== :: GetDependencyInformation -> GetDependencyInformation -> Bool
Eq, Int -> GetDependencyInformation -> ShowS
[GetDependencyInformation] -> ShowS
GetDependencyInformation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDependencyInformation] -> ShowS
$cshowList :: [GetDependencyInformation] -> ShowS
show :: GetDependencyInformation -> String
$cshow :: GetDependencyInformation -> String
showsPrec :: Int -> GetDependencyInformation -> ShowS
$cshowsPrec :: Int -> GetDependencyInformation -> ShowS
Show, Typeable, forall x.
Rep GetDependencyInformation x -> GetDependencyInformation
forall x.
GetDependencyInformation -> Rep GetDependencyInformation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetDependencyInformation x -> GetDependencyInformation
$cfrom :: forall x.
GetDependencyInformation -> Rep GetDependencyInformation x
Generic)
instance Hashable GetDependencyInformation
instance NFData   GetDependencyInformation

data GetModuleGraph = GetModuleGraph
    deriving (GetModuleGraph -> GetModuleGraph -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetModuleGraph -> GetModuleGraph -> Bool
$c/= :: GetModuleGraph -> GetModuleGraph -> Bool
== :: GetModuleGraph -> GetModuleGraph -> Bool
$c== :: GetModuleGraph -> GetModuleGraph -> Bool
Eq, Int -> GetModuleGraph -> ShowS
[GetModuleGraph] -> ShowS
GetModuleGraph -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetModuleGraph] -> ShowS
$cshowList :: [GetModuleGraph] -> ShowS
show :: GetModuleGraph -> String
$cshow :: GetModuleGraph -> String
showsPrec :: Int -> GetModuleGraph -> ShowS
$cshowsPrec :: Int -> GetModuleGraph -> ShowS
Show, Typeable, forall x. Rep GetModuleGraph x -> GetModuleGraph
forall x. GetModuleGraph -> Rep GetModuleGraph x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetModuleGraph x -> GetModuleGraph
$cfrom :: forall x. GetModuleGraph -> Rep GetModuleGraph x
Generic)
instance Hashable GetModuleGraph
instance NFData   GetModuleGraph

data ReportImportCycles = ReportImportCycles
    deriving (ReportImportCycles -> ReportImportCycles -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReportImportCycles -> ReportImportCycles -> Bool
$c/= :: ReportImportCycles -> ReportImportCycles -> Bool
== :: ReportImportCycles -> ReportImportCycles -> Bool
$c== :: ReportImportCycles -> ReportImportCycles -> Bool
Eq, Int -> ReportImportCycles -> ShowS
[ReportImportCycles] -> ShowS
ReportImportCycles -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReportImportCycles] -> ShowS
$cshowList :: [ReportImportCycles] -> ShowS
show :: ReportImportCycles -> String
$cshow :: ReportImportCycles -> String
showsPrec :: Int -> ReportImportCycles -> ShowS
$cshowsPrec :: Int -> ReportImportCycles -> ShowS
Show, Typeable, forall x. Rep ReportImportCycles x -> ReportImportCycles
forall x. ReportImportCycles -> Rep ReportImportCycles x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReportImportCycles x -> ReportImportCycles
$cfrom :: forall x. ReportImportCycles -> Rep ReportImportCycles x
Generic)
instance Hashable ReportImportCycles
instance NFData   ReportImportCycles

data TypeCheck = TypeCheck
    deriving (TypeCheck -> TypeCheck -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeCheck -> TypeCheck -> Bool
$c/= :: TypeCheck -> TypeCheck -> Bool
== :: TypeCheck -> TypeCheck -> Bool
$c== :: TypeCheck -> TypeCheck -> Bool
Eq, Int -> TypeCheck -> ShowS
[TypeCheck] -> ShowS
TypeCheck -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TypeCheck] -> ShowS
$cshowList :: [TypeCheck] -> ShowS
show :: TypeCheck -> String
$cshow :: TypeCheck -> String
showsPrec :: Int -> TypeCheck -> ShowS
$cshowsPrec :: Int -> TypeCheck -> ShowS
Show, Typeable, forall x. Rep TypeCheck x -> TypeCheck
forall x. TypeCheck -> Rep TypeCheck x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TypeCheck x -> TypeCheck
$cfrom :: forall x. TypeCheck -> Rep TypeCheck x
Generic)
instance Hashable TypeCheck
instance NFData   TypeCheck

data GetDocMap = GetDocMap
    deriving (GetDocMap -> GetDocMap -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDocMap -> GetDocMap -> Bool
$c/= :: GetDocMap -> GetDocMap -> Bool
== :: GetDocMap -> GetDocMap -> Bool
$c== :: GetDocMap -> GetDocMap -> Bool
Eq, Int -> GetDocMap -> ShowS
[GetDocMap] -> ShowS
GetDocMap -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDocMap] -> ShowS
$cshowList :: [GetDocMap] -> ShowS
show :: GetDocMap -> String
$cshow :: GetDocMap -> String
showsPrec :: Int -> GetDocMap -> ShowS
$cshowsPrec :: Int -> GetDocMap -> ShowS
Show, Typeable, forall x. Rep GetDocMap x -> GetDocMap
forall x. GetDocMap -> Rep GetDocMap x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDocMap x -> GetDocMap
$cfrom :: forall x. GetDocMap -> Rep GetDocMap x
Generic)
instance Hashable GetDocMap
instance NFData   GetDocMap

data GetHieAst = GetHieAst
    deriving (GetHieAst -> GetHieAst -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetHieAst -> GetHieAst -> Bool
$c/= :: GetHieAst -> GetHieAst -> Bool
== :: GetHieAst -> GetHieAst -> Bool
$c== :: GetHieAst -> GetHieAst -> Bool
Eq, Int -> GetHieAst -> ShowS
[GetHieAst] -> ShowS
GetHieAst -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetHieAst] -> ShowS
$cshowList :: [GetHieAst] -> ShowS
show :: GetHieAst -> String
$cshow :: GetHieAst -> String
showsPrec :: Int -> GetHieAst -> ShowS
$cshowsPrec :: Int -> GetHieAst -> ShowS
Show, Typeable, forall x. Rep GetHieAst x -> GetHieAst
forall x. GetHieAst -> Rep GetHieAst x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetHieAst x -> GetHieAst
$cfrom :: forall x. GetHieAst -> Rep GetHieAst x
Generic)
instance Hashable GetHieAst
instance NFData   GetHieAst

data GetBindings = GetBindings
    deriving (GetBindings -> GetBindings -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBindings -> GetBindings -> Bool
$c/= :: GetBindings -> GetBindings -> Bool
== :: GetBindings -> GetBindings -> Bool
$c== :: GetBindings -> GetBindings -> Bool
Eq, Int -> GetBindings -> ShowS
[GetBindings] -> ShowS
GetBindings -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBindings] -> ShowS
$cshowList :: [GetBindings] -> ShowS
show :: GetBindings -> String
$cshow :: GetBindings -> String
showsPrec :: Int -> GetBindings -> ShowS
$cshowsPrec :: Int -> GetBindings -> ShowS
Show, Typeable, forall x. Rep GetBindings x -> GetBindings
forall x. GetBindings -> Rep GetBindings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBindings x -> GetBindings
$cfrom :: forall x. GetBindings -> Rep GetBindings x
Generic)
instance Hashable GetBindings
instance NFData   GetBindings

data GhcSession = GhcSession
    deriving (GhcSession -> GhcSession -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GhcSession -> GhcSession -> Bool
$c/= :: GhcSession -> GhcSession -> Bool
== :: GhcSession -> GhcSession -> Bool
$c== :: GhcSession -> GhcSession -> Bool
Eq, Int -> GhcSession -> ShowS
[GhcSession] -> ShowS
GhcSession -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GhcSession] -> ShowS
$cshowList :: [GhcSession] -> ShowS
show :: GhcSession -> String
$cshow :: GhcSession -> String
showsPrec :: Int -> GhcSession -> ShowS
$cshowsPrec :: Int -> GhcSession -> ShowS
Show, Typeable, forall x. Rep GhcSession x -> GhcSession
forall x. GhcSession -> Rep GhcSession x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GhcSession x -> GhcSession
$cfrom :: forall x. GhcSession -> Rep GhcSession x
Generic)
instance Hashable GhcSession
instance NFData   GhcSession

newtype GhcSessionDeps = GhcSessionDeps_
    { -- | Load full ModSummary values in the GHC session.
        -- Required for interactive evaluation, but leads to more cache invalidations
        GhcSessionDeps -> Bool
fullModSummary :: Bool
    }
    deriving newtype (GhcSessionDeps -> GhcSessionDeps -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GhcSessionDeps -> GhcSessionDeps -> Bool
$c/= :: GhcSessionDeps -> GhcSessionDeps -> Bool
== :: GhcSessionDeps -> GhcSessionDeps -> Bool
$c== :: GhcSessionDeps -> GhcSessionDeps -> Bool
Eq, Typeable, Eq GhcSessionDeps
Int -> GhcSessionDeps -> Int
GhcSessionDeps -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: GhcSessionDeps -> Int
$chash :: GhcSessionDeps -> Int
hashWithSalt :: Int -> GhcSessionDeps -> Int
$chashWithSalt :: Int -> GhcSessionDeps -> Int
Hashable, GhcSessionDeps -> ()
forall a. (a -> ()) -> NFData a
rnf :: GhcSessionDeps -> ()
$crnf :: GhcSessionDeps -> ()
NFData)

instance Show GhcSessionDeps where
    show :: GhcSessionDeps -> String
show (GhcSessionDeps_ Bool
False) = String
"GhcSessionDeps"
    show (GhcSessionDeps_ Bool
True)  = String
"GhcSessionDepsFull"

pattern GhcSessionDeps :: GhcSessionDeps
pattern $bGhcSessionDeps :: GhcSessionDeps
$mGhcSessionDeps :: forall {r}. GhcSessionDeps -> ((# #) -> r) -> ((# #) -> r) -> r
GhcSessionDeps = GhcSessionDeps_ False

data GetModIfaceFromDisk = GetModIfaceFromDisk
    deriving (GetModIfaceFromDisk -> GetModIfaceFromDisk -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetModIfaceFromDisk -> GetModIfaceFromDisk -> Bool
$c/= :: GetModIfaceFromDisk -> GetModIfaceFromDisk -> Bool
== :: GetModIfaceFromDisk -> GetModIfaceFromDisk -> Bool
$c== :: GetModIfaceFromDisk -> GetModIfaceFromDisk -> Bool
Eq, Int -> GetModIfaceFromDisk -> ShowS
[GetModIfaceFromDisk] -> ShowS
GetModIfaceFromDisk -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetModIfaceFromDisk] -> ShowS
$cshowList :: [GetModIfaceFromDisk] -> ShowS
show :: GetModIfaceFromDisk -> String
$cshow :: GetModIfaceFromDisk -> String
showsPrec :: Int -> GetModIfaceFromDisk -> ShowS
$cshowsPrec :: Int -> GetModIfaceFromDisk -> ShowS
Show, Typeable, forall x. Rep GetModIfaceFromDisk x -> GetModIfaceFromDisk
forall x. GetModIfaceFromDisk -> Rep GetModIfaceFromDisk x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetModIfaceFromDisk x -> GetModIfaceFromDisk
$cfrom :: forall x. GetModIfaceFromDisk -> Rep GetModIfaceFromDisk x
Generic)
instance Hashable GetModIfaceFromDisk
instance NFData   GetModIfaceFromDisk

data GetModIfaceFromDiskAndIndex = GetModIfaceFromDiskAndIndex
    deriving (GetModIfaceFromDiskAndIndex -> GetModIfaceFromDiskAndIndex -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetModIfaceFromDiskAndIndex -> GetModIfaceFromDiskAndIndex -> Bool
$c/= :: GetModIfaceFromDiskAndIndex -> GetModIfaceFromDiskAndIndex -> Bool
== :: GetModIfaceFromDiskAndIndex -> GetModIfaceFromDiskAndIndex -> Bool
$c== :: GetModIfaceFromDiskAndIndex -> GetModIfaceFromDiskAndIndex -> Bool
Eq, Int -> GetModIfaceFromDiskAndIndex -> ShowS
[GetModIfaceFromDiskAndIndex] -> ShowS
GetModIfaceFromDiskAndIndex -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetModIfaceFromDiskAndIndex] -> ShowS
$cshowList :: [GetModIfaceFromDiskAndIndex] -> ShowS
show :: GetModIfaceFromDiskAndIndex -> String
$cshow :: GetModIfaceFromDiskAndIndex -> String
showsPrec :: Int -> GetModIfaceFromDiskAndIndex -> ShowS
$cshowsPrec :: Int -> GetModIfaceFromDiskAndIndex -> ShowS
Show, Typeable, forall x.
Rep GetModIfaceFromDiskAndIndex x -> GetModIfaceFromDiskAndIndex
forall x.
GetModIfaceFromDiskAndIndex -> Rep GetModIfaceFromDiskAndIndex x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetModIfaceFromDiskAndIndex x -> GetModIfaceFromDiskAndIndex
$cfrom :: forall x.
GetModIfaceFromDiskAndIndex -> Rep GetModIfaceFromDiskAndIndex x
Generic)
instance Hashable GetModIfaceFromDiskAndIndex
instance NFData   GetModIfaceFromDiskAndIndex

data GetModIface = GetModIface
    deriving (GetModIface -> GetModIface -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetModIface -> GetModIface -> Bool
$c/= :: GetModIface -> GetModIface -> Bool
== :: GetModIface -> GetModIface -> Bool
$c== :: GetModIface -> GetModIface -> Bool
Eq, Int -> GetModIface -> ShowS
[GetModIface] -> ShowS
GetModIface -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetModIface] -> ShowS
$cshowList :: [GetModIface] -> ShowS
show :: GetModIface -> String
$cshow :: GetModIface -> String
showsPrec :: Int -> GetModIface -> ShowS
$cshowsPrec :: Int -> GetModIface -> ShowS
Show, Typeable, forall x. Rep GetModIface x -> GetModIface
forall x. GetModIface -> Rep GetModIface x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetModIface x -> GetModIface
$cfrom :: forall x. GetModIface -> Rep GetModIface x
Generic)
instance Hashable GetModIface
instance NFData   GetModIface

data IsFileOfInterest = IsFileOfInterest
    deriving (IsFileOfInterest -> IsFileOfInterest -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IsFileOfInterest -> IsFileOfInterest -> Bool
$c/= :: IsFileOfInterest -> IsFileOfInterest -> Bool
== :: IsFileOfInterest -> IsFileOfInterest -> Bool
$c== :: IsFileOfInterest -> IsFileOfInterest -> Bool
Eq, Int -> IsFileOfInterest -> ShowS
[IsFileOfInterest] -> ShowS
IsFileOfInterest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IsFileOfInterest] -> ShowS
$cshowList :: [IsFileOfInterest] -> ShowS
show :: IsFileOfInterest -> String
$cshow :: IsFileOfInterest -> String
showsPrec :: Int -> IsFileOfInterest -> ShowS
$cshowsPrec :: Int -> IsFileOfInterest -> ShowS
Show, Typeable, forall x. Rep IsFileOfInterest x -> IsFileOfInterest
forall x. IsFileOfInterest -> Rep IsFileOfInterest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IsFileOfInterest x -> IsFileOfInterest
$cfrom :: forall x. IsFileOfInterest -> Rep IsFileOfInterest x
Generic)
instance Hashable IsFileOfInterest
instance NFData   IsFileOfInterest

data GetModSummaryWithoutTimestamps = GetModSummaryWithoutTimestamps
    deriving (GetModSummaryWithoutTimestamps
-> GetModSummaryWithoutTimestamps -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetModSummaryWithoutTimestamps
-> GetModSummaryWithoutTimestamps -> Bool
$c/= :: GetModSummaryWithoutTimestamps
-> GetModSummaryWithoutTimestamps -> Bool
== :: GetModSummaryWithoutTimestamps
-> GetModSummaryWithoutTimestamps -> Bool
$c== :: GetModSummaryWithoutTimestamps
-> GetModSummaryWithoutTimestamps -> Bool
Eq, Int -> GetModSummaryWithoutTimestamps -> ShowS
[GetModSummaryWithoutTimestamps] -> ShowS
GetModSummaryWithoutTimestamps -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetModSummaryWithoutTimestamps] -> ShowS
$cshowList :: [GetModSummaryWithoutTimestamps] -> ShowS
show :: GetModSummaryWithoutTimestamps -> String
$cshow :: GetModSummaryWithoutTimestamps -> String
showsPrec :: Int -> GetModSummaryWithoutTimestamps -> ShowS
$cshowsPrec :: Int -> GetModSummaryWithoutTimestamps -> ShowS
Show, Typeable, forall x.
Rep GetModSummaryWithoutTimestamps x
-> GetModSummaryWithoutTimestamps
forall x.
GetModSummaryWithoutTimestamps
-> Rep GetModSummaryWithoutTimestamps x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetModSummaryWithoutTimestamps x
-> GetModSummaryWithoutTimestamps
$cfrom :: forall x.
GetModSummaryWithoutTimestamps
-> Rep GetModSummaryWithoutTimestamps x
Generic)
instance Hashable GetModSummaryWithoutTimestamps
instance NFData   GetModSummaryWithoutTimestamps

data GetModSummary = GetModSummary
    deriving (GetModSummary -> GetModSummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetModSummary -> GetModSummary -> Bool
$c/= :: GetModSummary -> GetModSummary -> Bool
== :: GetModSummary -> GetModSummary -> Bool
$c== :: GetModSummary -> GetModSummary -> Bool
Eq, Int -> GetModSummary -> ShowS
[GetModSummary] -> ShowS
GetModSummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetModSummary] -> ShowS
$cshowList :: [GetModSummary] -> ShowS
show :: GetModSummary -> String
$cshow :: GetModSummary -> String
showsPrec :: Int -> GetModSummary -> ShowS
$cshowsPrec :: Int -> GetModSummary -> ShowS
Show, Typeable, forall x. Rep GetModSummary x -> GetModSummary
forall x. GetModSummary -> Rep GetModSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetModSummary x -> GetModSummary
$cfrom :: forall x. GetModSummary -> Rep GetModSummary x
Generic)
instance Hashable GetModSummary
instance NFData   GetModSummary

-- | Get the vscode client settings stored in the ide state
data GetClientSettings = GetClientSettings
    deriving (GetClientSettings -> GetClientSettings -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetClientSettings -> GetClientSettings -> Bool
$c/= :: GetClientSettings -> GetClientSettings -> Bool
== :: GetClientSettings -> GetClientSettings -> Bool
$c== :: GetClientSettings -> GetClientSettings -> Bool
Eq, Int -> GetClientSettings -> ShowS
[GetClientSettings] -> ShowS
GetClientSettings -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetClientSettings] -> ShowS
$cshowList :: [GetClientSettings] -> ShowS
show :: GetClientSettings -> String
$cshow :: GetClientSettings -> String
showsPrec :: Int -> GetClientSettings -> ShowS
$cshowsPrec :: Int -> GetClientSettings -> ShowS
Show, Typeable, forall x. Rep GetClientSettings x -> GetClientSettings
forall x. GetClientSettings -> Rep GetClientSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetClientSettings x -> GetClientSettings
$cfrom :: forall x. GetClientSettings -> Rep GetClientSettings x
Generic)
instance Hashable GetClientSettings
instance NFData   GetClientSettings

type instance RuleResult GetClientSettings = Hashed (Maybe Value)

data AddWatchedFile = AddWatchedFile deriving (AddWatchedFile -> AddWatchedFile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddWatchedFile -> AddWatchedFile -> Bool
$c/= :: AddWatchedFile -> AddWatchedFile -> Bool
== :: AddWatchedFile -> AddWatchedFile -> Bool
$c== :: AddWatchedFile -> AddWatchedFile -> Bool
Eq, Int -> AddWatchedFile -> ShowS
[AddWatchedFile] -> ShowS
AddWatchedFile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddWatchedFile] -> ShowS
$cshowList :: [AddWatchedFile] -> ShowS
show :: AddWatchedFile -> String
$cshow :: AddWatchedFile -> String
showsPrec :: Int -> AddWatchedFile -> ShowS
$cshowsPrec :: Int -> AddWatchedFile -> ShowS
Show, Typeable, forall x. Rep AddWatchedFile x -> AddWatchedFile
forall x. AddWatchedFile -> Rep AddWatchedFile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddWatchedFile x -> AddWatchedFile
$cfrom :: forall x. AddWatchedFile -> Rep AddWatchedFile x
Generic)
instance Hashable AddWatchedFile
instance NFData   AddWatchedFile


-- A local rule type to get caching. We want to use newCache, but it has
-- thread killed exception issues, so we lift it to a full rule.
-- https://github.com/digital-asset/daml/pull/2808#issuecomment-529639547
type instance RuleResult GhcSessionIO = IdeGhcSession

data IdeGhcSession = IdeGhcSession
  { IdeGhcSession -> String -> IO (IdeResult HscEnvEq, [String])
loadSessionFun :: FilePath -> IO (IdeResult HscEnvEq, [FilePath])
  -- ^ Returns the Ghc session and the cradle dependencies
  , IdeGhcSession -> Int
sessionVersion :: !Int
  -- ^ Used as Shake key, versions must be unique and not reused
  }

instance Show IdeGhcSession where show :: IdeGhcSession -> String
show IdeGhcSession
_ = String
"IdeGhcSession"
instance NFData IdeGhcSession where rnf :: IdeGhcSession -> ()
rnf !IdeGhcSession
_ = ()

data GhcSessionIO = GhcSessionIO deriving (GhcSessionIO -> GhcSessionIO -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GhcSessionIO -> GhcSessionIO -> Bool
$c/= :: GhcSessionIO -> GhcSessionIO -> Bool
== :: GhcSessionIO -> GhcSessionIO -> Bool
$c== :: GhcSessionIO -> GhcSessionIO -> Bool
Eq, Int -> GhcSessionIO -> ShowS
[GhcSessionIO] -> ShowS
GhcSessionIO -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GhcSessionIO] -> ShowS
$cshowList :: [GhcSessionIO] -> ShowS
show :: GhcSessionIO -> String
$cshow :: GhcSessionIO -> String
showsPrec :: Int -> GhcSessionIO -> ShowS
$cshowsPrec :: Int -> GhcSessionIO -> ShowS
Show, Typeable, forall x. Rep GhcSessionIO x -> GhcSessionIO
forall x. GhcSessionIO -> Rep GhcSessionIO x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GhcSessionIO x -> GhcSessionIO
$cfrom :: forall x. GhcSessionIO -> Rep GhcSessionIO x
Generic)
instance Hashable GhcSessionIO
instance NFData   GhcSessionIO

makeLensesWith
    (lensRules & lensField .~ mappingNamer (pure . (++ "L")))
    ''Splices