{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecursiveDo #-}
{-# LANGUAGE TypeFamilies #-}
module Development.IDE.Core.Shake(
IdeState, shakeSessionInit, shakeExtras, shakeDb,
ShakeExtras(..), getShakeExtras, getShakeExtrasRules,
KnownTargets, Target(..), toKnownFiles,
IdeRule, IdeResult,
GetModificationTime(GetModificationTime, GetModificationTime_, missingFileDiagnostics),
shakeOpen, shakeShut,
shakeEnqueue,
newSession,
use, useNoFile, uses, useWithStaleFast, useWithStaleFast', delayedAction,
FastResult(..),
use_, useNoFile_, uses_,
useWithStale, usesWithStale,
useWithStale_, usesWithStale_,
BadDependency(..),
RuleBody(..),
define, defineNoDiagnostics,
defineEarlyCutoff,
defineNoFile, defineEarlyCutOffNoFile,
getDiagnostics,
mRunLspT, mRunLspTCallback,
getHiddenDiagnostics,
IsIdeGlobal, addIdeGlobal, addIdeGlobalExtras, getIdeGlobalState, getIdeGlobalAction,
getIdeGlobalExtras,
getIdeOptions,
getIdeOptionsIO,
GlobalIdeOptions(..),
HLS.getClientConfig,
getPluginConfig,
knownTargets,
setPriority,
ideLogger,
actionLogger,
getVirtualFile,
FileVersion(..),
Priority(..),
updatePositionMapping,
deleteValue, recordDirtyKeys,
WithProgressFunc, WithIndefiniteProgressFunc,
ProgressEvent(..),
DelayedAction, mkDelayedAction,
IdeAction(..), runIdeAction,
mkUpdater,
Q(..),
IndexQueue,
HieDb,
HieDbWriter(..),
addPersistentRule,
garbageCollectDirtyKeys,
garbageCollectDirtyKeysOlderThan,
Log(..),
VFSModified(..)
) where
import Control.Concurrent.Async
import Control.Concurrent.STM
import Control.Concurrent.STM.Stats (atomicallyNamed)
import Control.Concurrent.Strict
import Control.DeepSeq
import Control.Exception.Extra hiding (bracket_)
import Control.Monad.Extra
import Control.Monad.IO.Class
import Control.Monad.Reader
import Control.Monad.Trans.Maybe
import Data.Aeson (toJSON)
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.Char8 as BS8
import Data.Coerce (coerce)
import Data.Default
import Data.Dynamic
import Data.EnumMap.Strict (EnumMap)
import qualified Data.EnumMap.Strict as EM
import Data.Foldable (for_, toList)
import Data.Functor ((<&>))
import qualified Data.HashMap.Strict as HMap
import Data.HashSet (HashSet)
import qualified Data.HashSet as HSet
import Data.Hashable
import Data.IORef
import Data.List.Extra (foldl', partition,
takeEnd)
import qualified Data.Map.Strict as Map
import Data.Maybe
import qualified Data.SortedList as SL
import Data.String (fromString)
import qualified Data.Text as T
import Data.Time
import Data.Traversable
import Data.Tuple.Extra
import Data.Typeable
import Data.Unique
import Data.Vector (Vector)
import qualified Data.Vector as Vector
import Debug.Trace.Flags (userTracingEnabled)
import Development.IDE.Core.Debouncer
import Development.IDE.Core.FileUtils (getModTime)
import Development.IDE.Core.PositionMapping
import Development.IDE.Core.ProgressReporting
import Development.IDE.Core.RuleTypes
import Development.IDE.Core.Tracing
import Development.IDE.GHC.Compat (NameCache,
NameCacheUpdater (..),
initNameCache,
knownKeyNames,
mkSplitUniqSupply,
upNameCache)
import Development.IDE.GHC.Orphans ()
import Development.IDE.Graph hiding (ShakeValue)
import qualified Development.IDE.Graph as Shake
import Development.IDE.Graph.Database (ShakeDatabase,
shakeGetBuildStep,
shakeNewDatabase,
shakeProfileDatabase,
shakeRunDatabaseForKeys)
import Development.IDE.Graph.Rule
import Development.IDE.Types.Action
import Development.IDE.Types.Diagnostics
import Development.IDE.Types.Exports
import qualified Development.IDE.Types.Exports as ExportsMap
import Development.IDE.Types.KnownTargets
import Development.IDE.Types.Location
import Development.IDE.Types.Logger hiding (Priority)
import qualified Development.IDE.Types.Logger as Logger
import Development.IDE.Types.Options
import Development.IDE.Types.Shake
import qualified Focus
import GHC.Fingerprint
import HieDb.Types
import Ide.Plugin.Config
import qualified Ide.PluginUtils as HLS
import Ide.Types (PluginId)
import Language.LSP.Diagnostics
import qualified Language.LSP.Server as LSP
import Language.LSP.Types
import qualified Language.LSP.Types as LSP
import Language.LSP.Types.Capabilities
import Language.LSP.VFS
import qualified "list-t" ListT
import OpenTelemetry.Eventlog
import qualified StmContainers.Map as STM
import System.FilePath hiding (makeRelative)
import System.IO.Unsafe (unsafePerformIO)
import System.Time.Extra
data Log
= LogCreateHieDbExportsMapStart
| LogCreateHieDbExportsMapFinish !Int
| LogBuildSessionRestart !String ![DelayedActionInternal] !(HashSet Key) !Seconds !(Maybe FilePath)
| LogBuildSessionRestartTakingTooLong !Seconds
| LogDelayedAction !(DelayedAction ()) !Seconds
| LogBuildSessionFinish !(Maybe SomeException)
| LogDiagsDiffButNoLspEnv ![FileDiagnostic]
| LogDefineEarlyCutoffRuleNoDiagHasDiag !FileDiagnostic
| LogDefineEarlyCutoffRuleCustomNewnessHasDiag !FileDiagnostic
deriving Int -> Log -> ShowS
[Log] -> ShowS
Log -> String
(Int -> Log -> ShowS)
-> (Log -> String) -> ([Log] -> ShowS) -> Show Log
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Log] -> ShowS
$cshowList :: [Log] -> ShowS
show :: Log -> String
$cshow :: Log -> String
showsPrec :: Int -> Log -> ShowS
$cshowsPrec :: Int -> Log -> ShowS
Show
instance Pretty Log where
pretty :: Log -> Doc ann
pretty = \case
Log
LogCreateHieDbExportsMapStart ->
Doc ann
"Initializing exports map from hiedb"
LogCreateHieDbExportsMapFinish Int
exportsMapSize ->
Doc ann
"Done initializing exports map from hiedb. Size:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Int -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Int
exportsMapSize
LogBuildSessionRestart String
reason [DelayedActionInternal]
actionQueue HashSet Key
keyBackLog Seconds
abortDuration Maybe String
shakeProfilePath ->
[Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vcat
[ Doc ann
"Restarting build session due to" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty String
reason
, Doc ann
"Action Queue:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> [String] -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty ((DelayedActionInternal -> String)
-> [DelayedActionInternal] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map DelayedActionInternal -> String
forall a. DelayedAction a -> String
actionName [DelayedActionInternal]
actionQueue)
, Doc ann
"Keys:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> [String] -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty ((Key -> String) -> [Key] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Key -> String
forall a. Show a => a -> String
show ([Key] -> [String]) -> [Key] -> [String]
forall a b. (a -> b) -> a -> b
$ HashSet Key -> [Key]
forall a. HashSet a -> [a]
HSet.toList HashSet Key
keyBackLog)
, Doc ann
"Aborting previous build session took" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (Seconds -> String
showDuration Seconds
abortDuration) Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Maybe String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Maybe String
shakeProfilePath ]
LogBuildSessionRestartTakingTooLong Seconds
seconds ->
Doc ann
"Build restart is taking too long (" Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> Seconds -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Seconds
seconds Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> Doc ann
" seconds)"
LogDelayedAction DelayedActionInternal
delayedAction Seconds
duration ->
[Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
hsep
[ Doc ann
"Finished:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (DelayedActionInternal -> String
forall a. DelayedAction a -> String
actionName DelayedActionInternal
delayedAction)
, Doc ann
"Took:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (Seconds -> String
showDuration Seconds
duration) ]
LogBuildSessionFinish Maybe SomeException
e ->
[Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vcat
[ Doc ann
"Finished build session"
, Maybe String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty ((SomeException -> String) -> Maybe SomeException -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SomeException -> String
forall e. Exception e => e -> String
displayException Maybe SomeException
e) ]
LogDiagsDiffButNoLspEnv [FileDiagnostic]
fileDiagnostics ->
Doc ann
"updateFileDiagnostics published different from new diagnostics - file diagnostics:"
Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty ([FileDiagnostic] -> Text
showDiagnosticsColored [FileDiagnostic]
fileDiagnostics)
LogDefineEarlyCutoffRuleNoDiagHasDiag FileDiagnostic
fileDiagnostic ->
Doc ann
"defineEarlyCutoff RuleNoDiagnostics - file diagnostic:"
Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty ([FileDiagnostic] -> Text
showDiagnosticsColored [FileDiagnostic
fileDiagnostic])
LogDefineEarlyCutoffRuleCustomNewnessHasDiag FileDiagnostic
fileDiagnostic ->
Doc ann
"defineEarlyCutoff RuleWithCustomNewnessCheck - file diagnostic:"
Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty ([FileDiagnostic] -> Text
showDiagnosticsColored [FileDiagnostic
fileDiagnostic])
data HieDbWriter
= HieDbWriter
{ HieDbWriter -> IndexQueue
indexQueue :: IndexQueue
, HieDbWriter -> TVar (HashMap NormalizedFilePath Fingerprint)
indexPending :: TVar (HMap.HashMap NormalizedFilePath Fingerprint)
, HieDbWriter -> TVar Int
indexCompleted :: TVar Int
, HieDbWriter -> Var (Maybe ProgressToken)
indexProgressToken :: Var (Maybe LSP.ProgressToken)
}
type IndexQueue = TQueue (((HieDb -> IO ()) -> IO ()) -> IO ())
data =
{
:: Maybe (LSP.LanguageContextEnv Config)
, :: Debouncer NormalizedUri
, :: Logger
, :: TVar (HMap.HashMap TypeRep Dynamic)
, :: Values
, :: STMDiagnosticStore
, :: STMDiagnosticStore
, :: STM.Map NormalizedUri [Diagnostic]
, :: STM.Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
, :: ProgressReporting
, :: IdeTesting
,
:: VFSModified
-> String
-> [DelayedAction ()]
-> IO ()
, :: IORef NameCache
, :: TVar (Hashed KnownTargets)
, :: TVar ExportsMap
, :: ActionQueue
, :: ClientCapabilities
, :: WithHieDb
, :: HieDbWriter
, :: TVar (HMap.HashMap Key GetStalePersistent)
, :: TVar VFS
, :: Config
, :: TVar (HashSet Key)
}
type WithProgressFunc = forall a.
T.Text -> LSP.ProgressCancellable -> ((LSP.ProgressAmount -> IO ()) -> IO a) -> IO a
type WithIndefiniteProgressFunc = forall a.
T.Text -> LSP.ProgressCancellable -> IO a -> IO a
type GetStalePersistent = NormalizedFilePath -> IdeAction (Maybe (Dynamic,PositionDelta,TextDocumentVersion))
getShakeExtras :: Action ShakeExtras
= do
Just ShakeExtras
x <- Typeable ShakeExtras => Action (Maybe ShakeExtras)
forall a. Typeable a => Action (Maybe a)
getShakeExtra @ShakeExtras
ShakeExtras -> Action ShakeExtras
forall (m :: * -> *) a. Monad m => a -> m a
return ShakeExtras
x
getShakeExtrasRules :: Rules ShakeExtras
= do
Just ShakeExtras
x <- Typeable ShakeExtras => Rules (Maybe ShakeExtras)
forall a. Typeable a => Rules (Maybe a)
getShakeExtraRules @ShakeExtras
ShakeExtras -> Rules ShakeExtras
forall (m :: * -> *) a. Monad m => a -> m a
return ShakeExtras
x
getPluginConfig
:: LSP.MonadLsp Config m => PluginId -> m PluginConfig
getPluginConfig :: PluginId -> m PluginConfig
getPluginConfig PluginId
plugin = do
Config
config <- m Config
forall (m :: * -> *). MonadLsp Config m => m Config
HLS.getClientConfig
PluginConfig -> m PluginConfig
forall (m :: * -> *) a. Monad m => a -> m a
return (PluginConfig -> m PluginConfig) -> PluginConfig -> m PluginConfig
forall a b. (a -> b) -> a -> b
$ Config -> PluginId -> PluginConfig
HLS.configForPlugin Config
config PluginId
plugin
addPersistentRule :: IdeRule k v => k -> (NormalizedFilePath -> IdeAction (Maybe (v,PositionDelta,TextDocumentVersion))) -> Rules ()
addPersistentRule :: k
-> (NormalizedFilePath
-> IdeAction (Maybe (v, PositionDelta, TextDocumentVersion)))
-> Rules ()
addPersistentRule k
k NormalizedFilePath
-> IdeAction (Maybe (v, PositionDelta, TextDocumentVersion))
getVal = do
ShakeExtras{TVar (HashMap Key GetStalePersistent)
persistentKeys :: TVar (HashMap Key GetStalePersistent)
$sel:persistentKeys:ShakeExtras :: ShakeExtras -> TVar (HashMap Key GetStalePersistent)
persistentKeys} <- Rules ShakeExtras
getShakeExtrasRules
Rules () -> Rules ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Rules () -> Rules ()) -> Rules () -> Rules ()
forall a b. (a -> b) -> a -> b
$ IO () -> Rules ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Rules ()) -> IO () -> Rules ()
forall a b. (a -> b) -> a -> b
$ STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ TVar (HashMap Key GetStalePersistent)
-> (HashMap Key GetStalePersistent
-> HashMap Key GetStalePersistent)
-> STM ()
forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar (HashMap Key GetStalePersistent)
persistentKeys ((HashMap Key GetStalePersistent -> HashMap Key GetStalePersistent)
-> STM ())
-> (HashMap Key GetStalePersistent
-> HashMap Key GetStalePersistent)
-> STM ()
forall a b. (a -> b) -> a -> b
$ Key
-> GetStalePersistent
-> HashMap Key GetStalePersistent
-> HashMap Key GetStalePersistent
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HMap.insert (k -> Key
forall a. (Typeable a, Eq a, Hashable a, Show a) => a -> Key
Key k
k) ((Maybe (v, PositionDelta, TextDocumentVersion)
-> Maybe (Dynamic, PositionDelta, TextDocumentVersion))
-> IdeAction (Maybe (v, PositionDelta, TextDocumentVersion))
-> IdeAction (Maybe (Dynamic, PositionDelta, TextDocumentVersion))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((v, PositionDelta, TextDocumentVersion)
-> (Dynamic, PositionDelta, TextDocumentVersion))
-> Maybe (v, PositionDelta, TextDocumentVersion)
-> Maybe (Dynamic, PositionDelta, TextDocumentVersion)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((v -> Dynamic)
-> (v, PositionDelta, TextDocumentVersion)
-> (Dynamic, PositionDelta, TextDocumentVersion)
forall a a' b c. (a -> a') -> (a, b, c) -> (a', b, c)
first3 v -> Dynamic
forall a. Typeable a => a -> Dynamic
toDyn)) (IdeAction (Maybe (v, PositionDelta, TextDocumentVersion))
-> IdeAction (Maybe (Dynamic, PositionDelta, TextDocumentVersion)))
-> (NormalizedFilePath
-> IdeAction (Maybe (v, PositionDelta, TextDocumentVersion)))
-> GetStalePersistent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NormalizedFilePath
-> IdeAction (Maybe (v, PositionDelta, TextDocumentVersion))
getVal)
class Typeable a => IsIdeGlobal a where
getVirtualFile :: NormalizedFilePath -> Action (Maybe VirtualFile)
getVirtualFile :: NormalizedFilePath -> Action (Maybe VirtualFile)
getVirtualFile NormalizedFilePath
nf = do
Map NormalizedUri VirtualFile
vfs <- (VFS -> Map NormalizedUri VirtualFile)
-> Action VFS -> Action (Map NormalizedUri VirtualFile)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap VFS -> Map NormalizedUri VirtualFile
vfsMap (Action VFS -> Action (Map NormalizedUri VirtualFile))
-> (ShakeExtras -> Action VFS)
-> ShakeExtras
-> Action (Map NormalizedUri VirtualFile)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO VFS -> Action VFS
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO VFS -> Action VFS)
-> (ShakeExtras -> IO VFS) -> ShakeExtras -> Action VFS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TVar VFS -> IO VFS
forall a. TVar a -> IO a
readTVarIO (TVar VFS -> IO VFS)
-> (ShakeExtras -> TVar VFS) -> ShakeExtras -> IO VFS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShakeExtras -> TVar VFS
vfsVar (ShakeExtras -> Action (Map NormalizedUri VirtualFile))
-> Action ShakeExtras -> Action (Map NormalizedUri VirtualFile)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Action ShakeExtras
getShakeExtras
Maybe VirtualFile -> Action (Maybe VirtualFile)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe VirtualFile -> Action (Maybe VirtualFile))
-> Maybe VirtualFile -> Action (Maybe VirtualFile)
forall a b. (a -> b) -> a -> b
$! NormalizedUri -> Map NormalizedUri VirtualFile -> Maybe VirtualFile
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (NormalizedFilePath -> NormalizedUri
filePathToUri' NormalizedFilePath
nf) Map NormalizedUri VirtualFile
vfs
vfsSnapshot :: Maybe (LSP.LanguageContextEnv a) -> IO VFS
vfsSnapshot :: Maybe (LanguageContextEnv a) -> IO VFS
vfsSnapshot Maybe (LanguageContextEnv a)
Nothing = VFS -> IO VFS
forall (f :: * -> *) a. Applicative f => a -> f a
pure (VFS -> IO VFS) -> VFS -> IO VFS
forall a b. (a -> b) -> a -> b
$ Map NormalizedUri VirtualFile -> String -> VFS
VFS Map NormalizedUri VirtualFile
forall a. Monoid a => a
mempty String
""
vfsSnapshot (Just LanguageContextEnv a
lspEnv) = LanguageContextEnv a -> LspT a IO VFS -> IO VFS
forall config (m :: * -> *) a.
LanguageContextEnv config -> LspT config m a -> m a
LSP.runLspT LanguageContextEnv a
lspEnv LspT a IO VFS
forall config (m :: * -> *). MonadLsp config m => m VFS
LSP.getVirtualFiles
addIdeGlobal :: IsIdeGlobal a => a -> Rules ()
addIdeGlobal :: a -> Rules ()
addIdeGlobal a
x = do
ShakeExtras
extras <- Rules ShakeExtras
getShakeExtrasRules
IO () -> Rules ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Rules ()) -> IO () -> Rules ()
forall a b. (a -> b) -> a -> b
$ ShakeExtras -> a -> IO ()
forall a. IsIdeGlobal a => ShakeExtras -> a -> IO ()
addIdeGlobalExtras ShakeExtras
extras a
x
addIdeGlobalExtras :: IsIdeGlobal a => ShakeExtras -> a -> IO ()
ShakeExtras{TVar (HashMap TypeRep Dynamic)
globals :: TVar (HashMap TypeRep Dynamic)
$sel:globals:ShakeExtras :: ShakeExtras -> TVar (HashMap TypeRep Dynamic)
globals} x :: a
x@(a -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf -> TypeRep
ty) =
IO () -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ IO () -> IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ TVar (HashMap TypeRep Dynamic)
-> (HashMap TypeRep Dynamic -> HashMap TypeRep Dynamic) -> STM ()
forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar (HashMap TypeRep Dynamic)
globals ((HashMap TypeRep Dynamic -> HashMap TypeRep Dynamic) -> STM ())
-> (HashMap TypeRep Dynamic -> HashMap TypeRep Dynamic) -> STM ()
forall a b. (a -> b) -> a -> b
$ \HashMap TypeRep Dynamic
mp -> case TypeRep -> HashMap TypeRep Dynamic -> Maybe Dynamic
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HMap.lookup TypeRep
ty HashMap TypeRep Dynamic
mp of
Just Dynamic
_ -> String -> HashMap TypeRep Dynamic
forall a. HasCallStack => String -> a
error (String -> HashMap TypeRep Dynamic)
-> String -> HashMap TypeRep Dynamic
forall a b. (a -> b) -> a -> b
$ String
"Internal error, addIdeGlobalExtras, got the same type twice for " String -> ShowS
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show TypeRep
ty
Maybe Dynamic
Nothing -> TypeRep
-> Dynamic -> HashMap TypeRep Dynamic -> HashMap TypeRep Dynamic
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HMap.insert TypeRep
ty (a -> Dynamic
forall a. Typeable a => a -> Dynamic
toDyn a
x) HashMap TypeRep Dynamic
mp
getIdeGlobalExtras :: forall a . IsIdeGlobal a => ShakeExtras -> IO a
ShakeExtras{TVar (HashMap TypeRep Dynamic)
globals :: TVar (HashMap TypeRep Dynamic)
$sel:globals:ShakeExtras :: ShakeExtras -> TVar (HashMap TypeRep Dynamic)
globals} = do
let typ :: TypeRep
typ = Proxy a -> TypeRep
forall k (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (Proxy a
forall k (t :: k). Proxy t
Proxy :: Proxy a)
Maybe Dynamic
x <- TypeRep -> HashMap TypeRep Dynamic -> Maybe Dynamic
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HMap.lookup (Proxy a -> TypeRep
forall k (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (Proxy a
forall k (t :: k). Proxy t
Proxy :: Proxy a)) (HashMap TypeRep Dynamic -> Maybe Dynamic)
-> IO (HashMap TypeRep Dynamic) -> IO (Maybe Dynamic)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TVar (HashMap TypeRep Dynamic) -> IO (HashMap TypeRep Dynamic)
forall a. TVar a -> IO a
readTVarIO TVar (HashMap TypeRep Dynamic)
globals
case Maybe Dynamic
x of
Just Dynamic
x
| Just a
x <- Dynamic -> Maybe a
forall a. Typeable a => Dynamic -> Maybe a
fromDynamic Dynamic
x -> a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x
| Bool
otherwise -> String -> IO a
forall a. HasCallStack => String -> IO a
errorIO (String -> IO a) -> String -> IO a
forall a b. (a -> b) -> a -> b
$ String
"Internal error, getIdeGlobalExtras, wrong type for " String -> ShowS
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show TypeRep
typ String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" (got " String -> ShowS
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Dynamic -> TypeRep
dynTypeRep Dynamic
x) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
Maybe Dynamic
Nothing -> String -> IO a
forall a. HasCallStack => String -> IO a
errorIO (String -> IO a) -> String -> IO a
forall a b. (a -> b) -> a -> b
$ String
"Internal error, getIdeGlobalExtras, no entry for " String -> ShowS
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show TypeRep
typ
getIdeGlobalAction :: forall a . IsIdeGlobal a => Action a
getIdeGlobalAction :: Action a
getIdeGlobalAction = IO a -> Action a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO a -> Action a)
-> (ShakeExtras -> IO a) -> ShakeExtras -> Action a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShakeExtras -> IO a
forall a. IsIdeGlobal a => ShakeExtras -> IO a
getIdeGlobalExtras (ShakeExtras -> Action a) -> Action ShakeExtras -> Action a
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Action ShakeExtras
getShakeExtras
getIdeGlobalState :: forall a . IsIdeGlobal a => IdeState -> IO a
getIdeGlobalState :: IdeState -> IO a
getIdeGlobalState = ShakeExtras -> IO a
forall a. IsIdeGlobal a => ShakeExtras -> IO a
getIdeGlobalExtras (ShakeExtras -> IO a)
-> (IdeState -> ShakeExtras) -> IdeState -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IdeState -> ShakeExtras
shakeExtras
newtype GlobalIdeOptions = GlobalIdeOptions IdeOptions
instance IsIdeGlobal GlobalIdeOptions
getIdeOptions :: Action IdeOptions
getIdeOptions :: Action IdeOptions
getIdeOptions = do
GlobalIdeOptions IdeOptions
x <- Action GlobalIdeOptions
forall a. IsIdeGlobal a => Action a
getIdeGlobalAction
Maybe (LanguageContextEnv Config)
env <- ShakeExtras -> Maybe (LanguageContextEnv Config)
lspEnv (ShakeExtras -> Maybe (LanguageContextEnv Config))
-> Action ShakeExtras -> Action (Maybe (LanguageContextEnv Config))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Action ShakeExtras
getShakeExtras
case Maybe (LanguageContextEnv Config)
env of
Maybe (LanguageContextEnv Config)
Nothing -> IdeOptions -> Action IdeOptions
forall (m :: * -> *) a. Monad m => a -> m a
return IdeOptions
x
Just LanguageContextEnv Config
env -> do
Config
config <- IO Config -> Action Config
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Config -> Action Config) -> IO Config -> Action Config
forall a b. (a -> b) -> a -> b
$ LanguageContextEnv Config -> LspT Config IO Config -> IO Config
forall config (m :: * -> *) a.
LanguageContextEnv config -> LspT config m a -> m a
LSP.runLspT LanguageContextEnv Config
env LspT Config IO Config
forall (m :: * -> *). MonadLsp Config m => m Config
HLS.getClientConfig
IdeOptions -> Action IdeOptions
forall (m :: * -> *) a. Monad m => a -> m a
return IdeOptions
x{optCheckProject :: IO Bool
optCheckProject = Bool -> IO Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ Config -> Bool
checkProject Config
config,
optCheckParents :: IO CheckParents
optCheckParents = CheckParents -> IO CheckParents
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CheckParents -> IO CheckParents)
-> CheckParents -> IO CheckParents
forall a b. (a -> b) -> a -> b
$ Config -> CheckParents
checkParents Config
config
}
getIdeOptionsIO :: ShakeExtras -> IO IdeOptions
getIdeOptionsIO :: ShakeExtras -> IO IdeOptions
getIdeOptionsIO ShakeExtras
ide = do
GlobalIdeOptions IdeOptions
x <- ShakeExtras -> IO GlobalIdeOptions
forall a. IsIdeGlobal a => ShakeExtras -> IO a
getIdeGlobalExtras ShakeExtras
ide
IdeOptions -> IO IdeOptions
forall (m :: * -> *) a. Monad m => a -> m a
return IdeOptions
x
lastValueIO :: IdeRule k v => ShakeExtras -> k -> NormalizedFilePath -> IO (Maybe (v, PositionMapping))
lastValueIO :: ShakeExtras
-> k -> NormalizedFilePath -> IO (Maybe (v, PositionMapping))
lastValueIO s :: ShakeExtras
s@ShakeExtras{Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
positionMapping :: Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
$sel:positionMapping:ShakeExtras :: ShakeExtras
-> Map
NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
positionMapping,TVar (HashMap Key GetStalePersistent)
persistentKeys :: TVar (HashMap Key GetStalePersistent)
$sel:persistentKeys:ShakeExtras :: ShakeExtras -> TVar (HashMap Key GetStalePersistent)
persistentKeys,Values
state :: Values
$sel:state:ShakeExtras :: ShakeExtras -> Values
state} k
k NormalizedFilePath
file = do
let readPersistent :: IO (Maybe (v, PositionMapping))
readPersistent
| IdeTesting Bool
testing <- ShakeExtras -> IdeTesting
ideTesting ShakeExtras
s
, Bool
testing = Maybe (v, PositionMapping) -> IO (Maybe (v, PositionMapping))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (v, PositionMapping)
forall a. Maybe a
Nothing
| Bool
otherwise = do
HashMap Key GetStalePersistent
pmap <- TVar (HashMap Key GetStalePersistent)
-> IO (HashMap Key GetStalePersistent)
forall a. TVar a -> IO a
readTVarIO TVar (HashMap Key GetStalePersistent)
persistentKeys
Maybe (v, PositionDelta, TextDocumentVersion)
mv <- MaybeT IO (v, PositionDelta, TextDocumentVersion)
-> IO (Maybe (v, PositionDelta, TextDocumentVersion))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT IO (v, PositionDelta, TextDocumentVersion)
-> IO (Maybe (v, PositionDelta, TextDocumentVersion)))
-> MaybeT IO (v, PositionDelta, TextDocumentVersion)
-> IO (Maybe (v, PositionDelta, TextDocumentVersion))
forall a b. (a -> b) -> a -> b
$ do
IO () -> MaybeT IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> MaybeT IO ()) -> IO () -> MaybeT IO ()
forall a b. (a -> b) -> a -> b
$ Logger -> Text -> IO ()
Logger.logDebug (ShakeExtras -> Logger
logger ShakeExtras
s) (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"LOOKUP UP PERSISTENT FOR: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ k -> String
forall a. Show a => a -> String
show k
k
GetStalePersistent
f <- IO (Maybe GetStalePersistent) -> MaybeT IO GetStalePersistent
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (IO (Maybe GetStalePersistent) -> MaybeT IO GetStalePersistent)
-> IO (Maybe GetStalePersistent) -> MaybeT IO GetStalePersistent
forall a b. (a -> b) -> a -> b
$ Maybe GetStalePersistent -> IO (Maybe GetStalePersistent)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe GetStalePersistent -> IO (Maybe GetStalePersistent))
-> Maybe GetStalePersistent -> IO (Maybe GetStalePersistent)
forall a b. (a -> b) -> a -> b
$ Key -> HashMap Key GetStalePersistent -> Maybe GetStalePersistent
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HMap.lookup (k -> Key
forall a. (Typeable a, Eq a, Hashable a, Show a) => a -> Key
Key k
k) HashMap Key GetStalePersistent
pmap
(Dynamic
dv,PositionDelta
del,TextDocumentVersion
ver) <- IO (Maybe (Dynamic, PositionDelta, TextDocumentVersion))
-> MaybeT IO (Dynamic, PositionDelta, TextDocumentVersion)
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (IO (Maybe (Dynamic, PositionDelta, TextDocumentVersion))
-> MaybeT IO (Dynamic, PositionDelta, TextDocumentVersion))
-> IO (Maybe (Dynamic, PositionDelta, TextDocumentVersion))
-> MaybeT IO (Dynamic, PositionDelta, TextDocumentVersion)
forall a b. (a -> b) -> a -> b
$ String
-> ShakeExtras
-> IdeAction (Maybe (Dynamic, PositionDelta, TextDocumentVersion))
-> IO (Maybe (Dynamic, PositionDelta, TextDocumentVersion))
forall a. String -> ShakeExtras -> IdeAction a -> IO a
runIdeAction String
"lastValueIO" ShakeExtras
s (IdeAction (Maybe (Dynamic, PositionDelta, TextDocumentVersion))
-> IO (Maybe (Dynamic, PositionDelta, TextDocumentVersion)))
-> IdeAction (Maybe (Dynamic, PositionDelta, TextDocumentVersion))
-> IO (Maybe (Dynamic, PositionDelta, TextDocumentVersion))
forall a b. (a -> b) -> a -> b
$ GetStalePersistent
f NormalizedFilePath
file
IO (Maybe (v, PositionDelta, TextDocumentVersion))
-> MaybeT IO (v, PositionDelta, TextDocumentVersion)
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (IO (Maybe (v, PositionDelta, TextDocumentVersion))
-> MaybeT IO (v, PositionDelta, TextDocumentVersion))
-> IO (Maybe (v, PositionDelta, TextDocumentVersion))
-> MaybeT IO (v, PositionDelta, TextDocumentVersion)
forall a b. (a -> b) -> a -> b
$ Maybe (v, PositionDelta, TextDocumentVersion)
-> IO (Maybe (v, PositionDelta, TextDocumentVersion))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (v, PositionDelta, TextDocumentVersion)
-> IO (Maybe (v, PositionDelta, TextDocumentVersion)))
-> Maybe (v, PositionDelta, TextDocumentVersion)
-> IO (Maybe (v, PositionDelta, TextDocumentVersion))
forall a b. (a -> b) -> a -> b
$ (,PositionDelta
del,TextDocumentVersion
ver) (v -> (v, PositionDelta, TextDocumentVersion))
-> Maybe v -> Maybe (v, PositionDelta, TextDocumentVersion)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Dynamic -> Maybe v
forall a. Typeable a => Dynamic -> Maybe a
fromDynamic Dynamic
dv
case Maybe (v, PositionDelta, TextDocumentVersion)
mv of
Maybe (v, PositionDelta, TextDocumentVersion)
Nothing -> String
-> STM (Maybe (v, PositionMapping))
-> IO (Maybe (v, PositionMapping))
forall a. String -> STM a -> IO a
atomicallyNamed String
"lastValueIO 1" (STM (Maybe (v, PositionMapping))
-> IO (Maybe (v, PositionMapping)))
-> STM (Maybe (v, PositionMapping))
-> IO (Maybe (v, PositionMapping))
forall a b. (a -> b) -> a -> b
$ do
Focus ValueWithDiagnostics STM () -> Key -> Values -> STM ()
forall key value result.
(Eq key, Hashable key) =>
Focus value STM result -> key -> Map key value -> STM result
STM.focus ((Maybe ValueWithDiagnostics -> Maybe ValueWithDiagnostics)
-> Focus ValueWithDiagnostics STM ()
forall (m :: * -> *) a.
Monad m =>
(Maybe a -> Maybe a) -> Focus a m ()
Focus.alter (Value Dynamic
-> Maybe ValueWithDiagnostics -> Maybe ValueWithDiagnostics
alterValue (Value Dynamic
-> Maybe ValueWithDiagnostics -> Maybe ValueWithDiagnostics)
-> Value Dynamic
-> Maybe ValueWithDiagnostics
-> Maybe ValueWithDiagnostics
forall a b. (a -> b) -> a -> b
$ Bool -> Value Dynamic
forall v. Bool -> Value v
Failed Bool
True)) (k -> NormalizedFilePath -> Key
forall k. ShakeValue k => k -> NormalizedFilePath -> Key
toKey k
k NormalizedFilePath
file) Values
state
Maybe (v, PositionMapping) -> STM (Maybe (v, PositionMapping))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (v, PositionMapping)
forall a. Maybe a
Nothing
Just (v
v,PositionDelta
del,TextDocumentVersion
ver) -> do
Maybe FileVersion
actual_version <- case TextDocumentVersion
ver of
Just Int32
ver -> Maybe FileVersion -> IO (Maybe FileVersion)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FileVersion -> Maybe FileVersion
forall a. a -> Maybe a
Just (FileVersion -> Maybe FileVersion)
-> FileVersion -> Maybe FileVersion
forall a b. (a -> b) -> a -> b
$ Int32 -> FileVersion
VFSVersion Int32
ver)
TextDocumentVersion
Nothing -> (FileVersion -> Maybe FileVersion
forall a. a -> Maybe a
Just (FileVersion -> Maybe FileVersion)
-> (POSIXTime -> FileVersion) -> POSIXTime -> Maybe FileVersion
forall b c a. (b -> c) -> (a -> b) -> a -> c
. POSIXTime -> FileVersion
ModificationTime (POSIXTime -> Maybe FileVersion)
-> IO POSIXTime -> IO (Maybe FileVersion)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO POSIXTime
getModTime (NormalizedFilePath -> String
fromNormalizedFilePath NormalizedFilePath
file))
IO (Maybe FileVersion)
-> (IOException -> IO (Maybe FileVersion))
-> IO (Maybe FileVersion)
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch` (\(IOException
_ :: IOException) -> Maybe FileVersion -> IO (Maybe FileVersion)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe FileVersion
forall a. Maybe a
Nothing)
String
-> STM (Maybe (v, PositionMapping))
-> IO (Maybe (v, PositionMapping))
forall a. String -> STM a -> IO a
atomicallyNamed String
"lastValueIO 2" (STM (Maybe (v, PositionMapping))
-> IO (Maybe (v, PositionMapping)))
-> STM (Maybe (v, PositionMapping))
-> IO (Maybe (v, PositionMapping))
forall a b. (a -> b) -> a -> b
$ do
Focus ValueWithDiagnostics STM () -> Key -> Values -> STM ()
forall key value result.
(Eq key, Hashable key) =>
Focus value STM result -> key -> Map key value -> STM result
STM.focus ((Maybe ValueWithDiagnostics -> Maybe ValueWithDiagnostics)
-> Focus ValueWithDiagnostics STM ()
forall (m :: * -> *) a.
Monad m =>
(Maybe a -> Maybe a) -> Focus a m ()
Focus.alter (Value Dynamic
-> Maybe ValueWithDiagnostics -> Maybe ValueWithDiagnostics
alterValue (Value Dynamic
-> Maybe ValueWithDiagnostics -> Maybe ValueWithDiagnostics)
-> Value Dynamic
-> Maybe ValueWithDiagnostics
-> Maybe ValueWithDiagnostics
forall a b. (a -> b) -> a -> b
$ Maybe PositionDelta
-> Maybe FileVersion -> Dynamic -> Value Dynamic
forall v. Maybe PositionDelta -> Maybe FileVersion -> v -> Value v
Stale (PositionDelta -> Maybe PositionDelta
forall a. a -> Maybe a
Just PositionDelta
del) Maybe FileVersion
actual_version (v -> Dynamic
forall a. Typeable a => a -> Dynamic
toDyn v
v))) (k -> NormalizedFilePath -> Key
forall k. ShakeValue k => k -> NormalizedFilePath -> Key
toKey k
k NormalizedFilePath
file) Values
state
(v, PositionMapping) -> Maybe (v, PositionMapping)
forall a. a -> Maybe a
Just ((v, PositionMapping) -> Maybe (v, PositionMapping))
-> (PositionMapping -> (v, PositionMapping))
-> PositionMapping
-> Maybe (v, PositionMapping)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (v
v,) (PositionMapping -> (v, PositionMapping))
-> (PositionMapping -> PositionMapping)
-> PositionMapping
-> (v, PositionMapping)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PositionDelta -> PositionMapping -> PositionMapping
addDelta PositionDelta
del (PositionMapping -> Maybe (v, PositionMapping))
-> STM PositionMapping -> STM (Maybe (v, PositionMapping))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
-> NormalizedFilePath -> Maybe FileVersion -> STM PositionMapping
forall a.
Map NormalizedUri (EnumMap Int32 (a, PositionMapping))
-> NormalizedFilePath -> Maybe FileVersion -> STM PositionMapping
mappingForVersion Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
positionMapping NormalizedFilePath
file Maybe FileVersion
actual_version
alterValue :: Value Dynamic
-> Maybe ValueWithDiagnostics -> Maybe ValueWithDiagnostics
alterValue Value Dynamic
new Maybe ValueWithDiagnostics
Nothing = ValueWithDiagnostics -> Maybe ValueWithDiagnostics
forall a. a -> Maybe a
Just (Value Dynamic -> Vector FileDiagnostic -> ValueWithDiagnostics
ValueWithDiagnostics Value Dynamic
new Vector FileDiagnostic
forall a. Monoid a => a
mempty)
alterValue Value Dynamic
new (Just old :: ValueWithDiagnostics
old@(ValueWithDiagnostics Value Dynamic
val Vector FileDiagnostic
diags)) = ValueWithDiagnostics -> Maybe ValueWithDiagnostics
forall a. a -> Maybe a
Just (ValueWithDiagnostics -> Maybe ValueWithDiagnostics)
-> ValueWithDiagnostics -> Maybe ValueWithDiagnostics
forall a b. (a -> b) -> a -> b
$ case Value Dynamic
val of
Failed{} -> Value Dynamic -> Vector FileDiagnostic -> ValueWithDiagnostics
ValueWithDiagnostics Value Dynamic
new Vector FileDiagnostic
diags
Value Dynamic
_ -> ValueWithDiagnostics
old
String
-> STM (Maybe ValueWithDiagnostics)
-> IO (Maybe ValueWithDiagnostics)
forall a. String -> STM a -> IO a
atomicallyNamed String
"lastValueIO 4" (Key -> Values -> STM (Maybe ValueWithDiagnostics)
forall key value.
(Eq key, Hashable key) =>
key -> Map key value -> STM (Maybe value)
STM.lookup (k -> NormalizedFilePath -> Key
forall k. ShakeValue k => k -> NormalizedFilePath -> Key
toKey k
k NormalizedFilePath
file) Values
state) IO (Maybe ValueWithDiagnostics)
-> (Maybe ValueWithDiagnostics -> IO (Maybe (v, PositionMapping)))
-> IO (Maybe (v, PositionMapping))
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe ValueWithDiagnostics
Nothing -> IO (Maybe (v, PositionMapping))
readPersistent
Just (ValueWithDiagnostics Value Dynamic
v Vector FileDiagnostic
_) -> case Value Dynamic
v of
Succeeded Maybe FileVersion
ver (Dynamic -> Maybe v
forall a. Typeable a => Dynamic -> Maybe a
fromDynamic -> Just v
v) ->
String
-> STM (Maybe (v, PositionMapping))
-> IO (Maybe (v, PositionMapping))
forall a. String -> STM a -> IO a
atomicallyNamed String
"lastValueIO 5" (STM (Maybe (v, PositionMapping))
-> IO (Maybe (v, PositionMapping)))
-> STM (Maybe (v, PositionMapping))
-> IO (Maybe (v, PositionMapping))
forall a b. (a -> b) -> a -> b
$ (v, PositionMapping) -> Maybe (v, PositionMapping)
forall a. a -> Maybe a
Just ((v, PositionMapping) -> Maybe (v, PositionMapping))
-> (PositionMapping -> (v, PositionMapping))
-> PositionMapping
-> Maybe (v, PositionMapping)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (v
v,) (PositionMapping -> Maybe (v, PositionMapping))
-> STM PositionMapping -> STM (Maybe (v, PositionMapping))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
-> NormalizedFilePath -> Maybe FileVersion -> STM PositionMapping
forall a.
Map NormalizedUri (EnumMap Int32 (a, PositionMapping))
-> NormalizedFilePath -> Maybe FileVersion -> STM PositionMapping
mappingForVersion Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
positionMapping NormalizedFilePath
file Maybe FileVersion
ver
Stale Maybe PositionDelta
del Maybe FileVersion
ver (Dynamic -> Maybe v
forall a. Typeable a => Dynamic -> Maybe a
fromDynamic -> Just v
v) ->
String
-> STM (Maybe (v, PositionMapping))
-> IO (Maybe (v, PositionMapping))
forall a. String -> STM a -> IO a
atomicallyNamed String
"lastValueIO 6" (STM (Maybe (v, PositionMapping))
-> IO (Maybe (v, PositionMapping)))
-> STM (Maybe (v, PositionMapping))
-> IO (Maybe (v, PositionMapping))
forall a b. (a -> b) -> a -> b
$ (v, PositionMapping) -> Maybe (v, PositionMapping)
forall a. a -> Maybe a
Just ((v, PositionMapping) -> Maybe (v, PositionMapping))
-> (PositionMapping -> (v, PositionMapping))
-> PositionMapping
-> Maybe (v, PositionMapping)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (v
v,) (PositionMapping -> (v, PositionMapping))
-> (PositionMapping -> PositionMapping)
-> PositionMapping
-> (v, PositionMapping)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PositionMapping -> PositionMapping)
-> (PositionDelta -> PositionMapping -> PositionMapping)
-> Maybe PositionDelta
-> PositionMapping
-> PositionMapping
forall b a. b -> (a -> b) -> Maybe a -> b
maybe PositionMapping -> PositionMapping
forall a. a -> a
id PositionDelta -> PositionMapping -> PositionMapping
addDelta Maybe PositionDelta
del (PositionMapping -> Maybe (v, PositionMapping))
-> STM PositionMapping -> STM (Maybe (v, PositionMapping))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
-> NormalizedFilePath -> Maybe FileVersion -> STM PositionMapping
forall a.
Map NormalizedUri (EnumMap Int32 (a, PositionMapping))
-> NormalizedFilePath -> Maybe FileVersion -> STM PositionMapping
mappingForVersion Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
positionMapping NormalizedFilePath
file Maybe FileVersion
ver
Failed Bool
p | Bool -> Bool
not Bool
p -> IO (Maybe (v, PositionMapping))
readPersistent
Value Dynamic
_ -> Maybe (v, PositionMapping) -> IO (Maybe (v, PositionMapping))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (v, PositionMapping)
forall a. Maybe a
Nothing
lastValue :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping))
lastValue :: k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping))
lastValue k
key NormalizedFilePath
file = do
ShakeExtras
s <- Action ShakeExtras
getShakeExtras
IO (Maybe (v, PositionMapping))
-> Action (Maybe (v, PositionMapping))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe (v, PositionMapping))
-> Action (Maybe (v, PositionMapping)))
-> IO (Maybe (v, PositionMapping))
-> Action (Maybe (v, PositionMapping))
forall a b. (a -> b) -> a -> b
$ ShakeExtras
-> k -> NormalizedFilePath -> IO (Maybe (v, PositionMapping))
forall k v.
IdeRule k v =>
ShakeExtras
-> k -> NormalizedFilePath -> IO (Maybe (v, PositionMapping))
lastValueIO ShakeExtras
s k
key NormalizedFilePath
file
mappingForVersion
:: STM.Map NormalizedUri (EnumMap Int32 (a, PositionMapping))
-> NormalizedFilePath
-> Maybe FileVersion
-> STM PositionMapping
mappingForVersion :: Map NormalizedUri (EnumMap Int32 (a, PositionMapping))
-> NormalizedFilePath -> Maybe FileVersion -> STM PositionMapping
mappingForVersion Map NormalizedUri (EnumMap Int32 (a, PositionMapping))
allMappings NormalizedFilePath
file (Just (VFSVersion Int32
ver)) = do
Maybe (EnumMap Int32 (a, PositionMapping))
mapping <- NormalizedUri
-> Map NormalizedUri (EnumMap Int32 (a, PositionMapping))
-> STM (Maybe (EnumMap Int32 (a, PositionMapping)))
forall key value.
(Eq key, Hashable key) =>
key -> Map key value -> STM (Maybe value)
STM.lookup (NormalizedFilePath -> NormalizedUri
filePathToUri' NormalizedFilePath
file) Map NormalizedUri (EnumMap Int32 (a, PositionMapping))
allMappings
PositionMapping -> STM PositionMapping
forall (m :: * -> *) a. Monad m => a -> m a
return (PositionMapping -> STM PositionMapping)
-> PositionMapping -> STM PositionMapping
forall a b. (a -> b) -> a -> b
$ PositionMapping
-> ((a, PositionMapping) -> PositionMapping)
-> Maybe (a, PositionMapping)
-> PositionMapping
forall b a. b -> (a -> b) -> Maybe a -> b
maybe PositionMapping
zeroMapping (a, PositionMapping) -> PositionMapping
forall a b. (a, b) -> b
snd (Maybe (a, PositionMapping) -> PositionMapping)
-> Maybe (a, PositionMapping) -> PositionMapping
forall a b. (a -> b) -> a -> b
$ Int32
-> EnumMap Int32 (a, PositionMapping) -> Maybe (a, PositionMapping)
forall k a. Enum k => k -> EnumMap k a -> Maybe a
EM.lookup Int32
ver (EnumMap Int32 (a, PositionMapping) -> Maybe (a, PositionMapping))
-> Maybe (EnumMap Int32 (a, PositionMapping))
-> Maybe (a, PositionMapping)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe (EnumMap Int32 (a, PositionMapping))
mapping
mappingForVersion Map NormalizedUri (EnumMap Int32 (a, PositionMapping))
_ NormalizedFilePath
_ Maybe FileVersion
_ = PositionMapping -> STM PositionMapping
forall (f :: * -> *) a. Applicative f => a -> f a
pure PositionMapping
zeroMapping
type IdeRule k v =
( Shake.RuleResult k ~ v
, Shake.ShakeValue k
, Show v
, Typeable v
, NFData v
)
newtype ShakeSession = ShakeSession
{ ShakeSession -> IO ()
cancelShakeSession :: IO ()
}
data IdeState = IdeState
{IdeState -> ShakeDatabase
shakeDb :: ShakeDatabase
,IdeState -> MVar ShakeSession
shakeSession :: MVar ShakeSession
, :: ShakeExtras
,IdeState -> ShakeDatabase -> IO (Maybe String)
shakeDatabaseProfile :: ShakeDatabase -> IO (Maybe FilePath)
}
shakeDatabaseProfileIO :: Maybe FilePath -> IO(ShakeDatabase -> IO (Maybe FilePath))
shakeDatabaseProfileIO :: Maybe String -> IO (ShakeDatabase -> IO (Maybe String))
shakeDatabaseProfileIO Maybe String
mbProfileDir = do
String
profileStartTime <- TimeLocale -> String -> UTCTime -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
defaultTimeLocale String
"%Y%m%d-%H%M%S" (UTCTime -> String) -> IO UTCTime -> IO String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO UTCTime
getCurrentTime
Var Int
profileCounter <- Int -> IO (Var Int)
forall a. a -> IO (Var a)
newVar (Int
0::Int)
(ShakeDatabase -> IO (Maybe String))
-> IO (ShakeDatabase -> IO (Maybe String))
forall (m :: * -> *) a. Monad m => a -> m a
return ((ShakeDatabase -> IO (Maybe String))
-> IO (ShakeDatabase -> IO (Maybe String)))
-> (ShakeDatabase -> IO (Maybe String))
-> IO (ShakeDatabase -> IO (Maybe String))
forall a b. (a -> b) -> a -> b
$ \ShakeDatabase
shakeDb ->
Maybe String -> (String -> IO String) -> IO (Maybe String)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for Maybe String
mbProfileDir ((String -> IO String) -> IO (Maybe String))
-> (String -> IO String) -> IO (Maybe String)
forall a b. (a -> b) -> a -> b
$ \String
dir -> do
Int
count <- Var Int -> (Int -> IO (Int, Int)) -> IO Int
forall a b. Var a -> (a -> IO (a, b)) -> IO b
modifyVar Var Int
profileCounter ((Int -> IO (Int, Int)) -> IO Int)
-> (Int -> IO (Int, Int)) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Int
x -> let !y :: Int
y = Int
xInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1 in (Int, Int) -> IO (Int, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
y,Int
y)
let file :: String
file = String
"ide-" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
profileStartTime String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"-" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> ShowS
forall a. Int -> [a] -> [a]
takeEnd Int
5 (String
"0000" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
count) String -> ShowS
<.> String
"html"
ShakeDatabase -> String -> IO ()
shakeProfileDatabase ShakeDatabase
shakeDb (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
dir String -> ShowS
</> String
file
String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return (String
dir String -> ShowS
</> String
file)
setValues :: IdeRule k v
=> Values
-> k
-> NormalizedFilePath
-> Value v
-> Vector FileDiagnostic
-> STM ()
setValues :: Values
-> k
-> NormalizedFilePath
-> Value v
-> Vector FileDiagnostic
-> STM ()
setValues Values
state k
key NormalizedFilePath
file Value v
val Vector FileDiagnostic
diags =
ValueWithDiagnostics -> Key -> Values -> STM ()
forall key value.
(Eq key, Hashable key) =>
value -> key -> Map key value -> STM ()
STM.insert (Value Dynamic -> Vector FileDiagnostic -> ValueWithDiagnostics
ValueWithDiagnostics ((v -> Dynamic) -> Value v -> Value Dynamic
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap v -> Dynamic
forall a. Typeable a => a -> Dynamic
toDyn Value v
val) Vector FileDiagnostic
diags) (k -> NormalizedFilePath -> Key
forall k. ShakeValue k => k -> NormalizedFilePath -> Key
toKey k
key NormalizedFilePath
file) Values
state
deleteValue
:: Shake.ShakeValue k
=> ShakeExtras
-> k
-> NormalizedFilePath
-> STM ()
deleteValue :: ShakeExtras -> k -> NormalizedFilePath -> STM ()
deleteValue ShakeExtras{TVar (HashSet Key)
dirtyKeys :: TVar (HashSet Key)
$sel:dirtyKeys:ShakeExtras :: ShakeExtras -> TVar (HashSet Key)
dirtyKeys, Values
state :: Values
$sel:state:ShakeExtras :: ShakeExtras -> Values
state} k
key NormalizedFilePath
file = do
Key -> Values -> STM ()
forall key value.
(Eq key, Hashable key) =>
key -> Map key value -> STM ()
STM.delete (k -> NormalizedFilePath -> Key
forall k. ShakeValue k => k -> NormalizedFilePath -> Key
toKey k
key NormalizedFilePath
file) Values
state
TVar (HashSet Key) -> (HashSet Key -> HashSet Key) -> STM ()
forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar (HashSet Key)
dirtyKeys ((HashSet Key -> HashSet Key) -> STM ())
-> (HashSet Key -> HashSet Key) -> STM ()
forall a b. (a -> b) -> a -> b
$ Key -> HashSet Key -> HashSet Key
forall a. (Eq a, Hashable a) => a -> HashSet a -> HashSet a
HSet.insert (k -> NormalizedFilePath -> Key
forall k. ShakeValue k => k -> NormalizedFilePath -> Key
toKey k
key NormalizedFilePath
file)
recordDirtyKeys
:: Shake.ShakeValue k
=> ShakeExtras
-> k
-> [NormalizedFilePath]
-> STM (IO ())
recordDirtyKeys :: ShakeExtras -> k -> [NormalizedFilePath] -> STM (IO ())
recordDirtyKeys ShakeExtras{TVar (HashSet Key)
dirtyKeys :: TVar (HashSet Key)
$sel:dirtyKeys:ShakeExtras :: ShakeExtras -> TVar (HashSet Key)
dirtyKeys} k
key [NormalizedFilePath]
file = do
TVar (HashSet Key) -> (HashSet Key -> HashSet Key) -> STM ()
forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar (HashSet Key)
dirtyKeys ((HashSet Key -> HashSet Key) -> STM ())
-> (HashSet Key -> HashSet Key) -> STM ()
forall a b. (a -> b) -> a -> b
$ \HashSet Key
x -> (HashSet Key -> Key -> HashSet Key)
-> HashSet Key -> [Key] -> HashSet Key
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' ((Key -> HashSet Key -> HashSet Key)
-> HashSet Key -> Key -> HashSet Key
forall a b c. (a -> b -> c) -> b -> a -> c
flip Key -> HashSet Key -> HashSet Key
forall a. (Eq a, Hashable a) => a -> HashSet a -> HashSet a
HSet.insert) HashSet Key
x (k -> NormalizedFilePath -> Key
forall k. ShakeValue k => k -> NormalizedFilePath -> Key
toKey k
key (NormalizedFilePath -> Key) -> [NormalizedFilePath] -> [Key]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [NormalizedFilePath]
file)
IO () -> STM (IO ())
forall (m :: * -> *) a. Monad m => a -> m a
return (IO () -> STM (IO ())) -> IO () -> STM (IO ())
forall a b. (a -> b) -> a -> b
$ String -> ((ByteString -> IO ()) -> IO ()) -> IO ()
forall (m :: * -> *) a.
(MonadMask m, MonadIO m) =>
String -> ((ByteString -> m ()) -> m a) -> m a
withEventTrace String
"recordDirtyKeys" (((ByteString -> IO ()) -> IO ()) -> IO ())
-> ((ByteString -> IO ()) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ByteString -> IO ()
addEvent -> do
ByteString -> IO ()
addEvent (String -> ByteString
forall a. IsString a => String -> a
fromString (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ String
"dirty " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> k -> String
forall a. Show a => a -> String
show k
key String -> [String] -> [String]
forall a. a -> [a] -> [a]
: (NormalizedFilePath -> String) -> [NormalizedFilePath] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map NormalizedFilePath -> String
fromNormalizedFilePath [NormalizedFilePath]
file)
getValues ::
forall k v.
IdeRule k v =>
Values ->
k ->
NormalizedFilePath ->
STM (Maybe (Value v, Vector FileDiagnostic))
getValues :: Values
-> k
-> NormalizedFilePath
-> STM (Maybe (Value v, Vector FileDiagnostic))
getValues Values
state k
key NormalizedFilePath
file = do
Key -> Values -> STM (Maybe ValueWithDiagnostics)
forall key value.
(Eq key, Hashable key) =>
key -> Map key value -> STM (Maybe value)
STM.lookup (k -> NormalizedFilePath -> Key
forall k. ShakeValue k => k -> NormalizedFilePath -> Key
toKey k
key NormalizedFilePath
file) Values
state STM (Maybe ValueWithDiagnostics)
-> (Maybe ValueWithDiagnostics
-> STM (Maybe (Value v, Vector FileDiagnostic)))
-> STM (Maybe (Value v, Vector FileDiagnostic))
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe ValueWithDiagnostics
Nothing -> Maybe (Value v, Vector FileDiagnostic)
-> STM (Maybe (Value v, Vector FileDiagnostic))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (Value v, Vector FileDiagnostic)
forall a. Maybe a
Nothing
Just (ValueWithDiagnostics Value Dynamic
v Vector FileDiagnostic
diagsV) -> do
let !r :: Value v
r = Value v -> Value v
forall v. Value v -> Value v
seqValue (Value v -> Value v) -> Value v -> Value v
forall a b. (a -> b) -> a -> b
$ (Dynamic -> v) -> Value Dynamic -> Value v
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Maybe v -> v
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe v -> v) -> (Dynamic -> Maybe v) -> Dynamic -> v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Typeable v => Dynamic -> Maybe v
forall a. Typeable a => Dynamic -> Maybe a
fromDynamic @v) Value Dynamic
v
!res :: (Value v, Vector FileDiagnostic)
res = (Value v
r,Vector FileDiagnostic
diagsV)
Maybe (Value v, Vector FileDiagnostic)
-> STM (Maybe (Value v, Vector FileDiagnostic))
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe (Value v, Vector FileDiagnostic)
-> STM (Maybe (Value v, Vector FileDiagnostic)))
-> Maybe (Value v, Vector FileDiagnostic)
-> STM (Maybe (Value v, Vector FileDiagnostic))
forall a b. (a -> b) -> a -> b
$ (Value v, Vector FileDiagnostic)
-> Maybe (Value v, Vector FileDiagnostic)
forall a. a -> Maybe a
Just (Value v, Vector FileDiagnostic)
res
knownTargets :: Action (Hashed KnownTargets)
knownTargets :: Action (Hashed KnownTargets)
knownTargets = do
ShakeExtras{TVar (Hashed KnownTargets)
knownTargetsVar :: TVar (Hashed KnownTargets)
$sel:knownTargetsVar:ShakeExtras :: ShakeExtras -> TVar (Hashed KnownTargets)
knownTargetsVar} <- Action ShakeExtras
getShakeExtras
IO (Hashed KnownTargets) -> Action (Hashed KnownTargets)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Hashed KnownTargets) -> Action (Hashed KnownTargets))
-> IO (Hashed KnownTargets) -> Action (Hashed KnownTargets)
forall a b. (a -> b) -> a -> b
$ TVar (Hashed KnownTargets) -> IO (Hashed KnownTargets)
forall a. TVar a -> IO a
readTVarIO TVar (Hashed KnownTargets)
knownTargetsVar
seqValue :: Value v -> Value v
seqValue :: Value v -> Value v
seqValue Value v
val = case Value v
val of
Succeeded Maybe FileVersion
ver v
v -> Maybe FileVersion -> ()
forall a. NFData a => a -> ()
rnf Maybe FileVersion
ver () -> Value v -> Value v
`seq` v
v v -> Value v -> Value v
`seq` Value v
val
Stale Maybe PositionDelta
d Maybe FileVersion
ver v
v -> Maybe PositionDelta -> ()
forall a. NFData a => a -> ()
rnf Maybe PositionDelta
d () -> Value v -> Value v
`seq` Maybe FileVersion -> ()
forall a. NFData a => a -> ()
rnf Maybe FileVersion
ver () -> Value v -> Value v
`seq` v
v v -> Value v -> Value v
`seq` Value v
val
Failed Bool
_ -> Value v
val
shakeOpen :: Recorder (WithPriority Log)
-> Maybe (LSP.LanguageContextEnv Config)
-> Config
-> Logger
-> Debouncer NormalizedUri
-> Maybe FilePath
-> IdeReportProgress
-> IdeTesting
-> WithHieDb
-> IndexQueue
-> ShakeOptions
-> Rules ()
-> IO IdeState
shakeOpen :: Recorder (WithPriority Log)
-> Maybe (LanguageContextEnv Config)
-> Config
-> Logger
-> Debouncer NormalizedUri
-> Maybe String
-> IdeReportProgress
-> IdeTesting
-> (forall a. (HieDb -> IO a) -> IO a)
-> IndexQueue
-> ShakeOptions
-> Rules ()
-> IO IdeState
shakeOpen Recorder (WithPriority Log)
recorder Maybe (LanguageContextEnv Config)
lspEnv Config
defaultConfig Logger
logger Debouncer NormalizedUri
debouncer
Maybe String
shakeProfileDir (IdeReportProgress Bool
reportProgress) ideTesting :: IdeTesting
ideTesting@(IdeTesting Bool
testing) forall a. (HieDb -> IO a) -> IO a
withHieDb IndexQueue
indexQueue ShakeOptions
opts Rules ()
rules = mdo
let log :: Logger.Priority -> Log -> IO ()
log :: Priority -> Log -> IO ()
log = Recorder (WithPriority Log) -> Priority -> Log -> IO ()
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder
UniqSupply
us <- Char -> IO UniqSupply
mkSplitUniqSupply Char
'r'
IORef NameCache
ideNc <- NameCache -> IO (IORef NameCache)
forall a. a -> IO (IORef a)
newIORef (UniqSupply -> [Name] -> NameCache
initNameCache UniqSupply
us [Name]
knownKeyNames)
ShakeExtras
shakeExtras <- do
TVar (HashMap TypeRep Dynamic)
globals <- HashMap TypeRep Dynamic -> IO (TVar (HashMap TypeRep Dynamic))
forall a. a -> IO (TVar a)
newTVarIO HashMap TypeRep Dynamic
forall k v. HashMap k v
HMap.empty
Values
state <- IO Values
forall key value. IO (Map key value)
STM.newIO
STMDiagnosticStore
diagnostics <- IO STMDiagnosticStore
forall key value. IO (Map key value)
STM.newIO
STMDiagnosticStore
hiddenDiagnostics <- IO STMDiagnosticStore
forall key value. IO (Map key value)
STM.newIO
Map NormalizedUri [Diagnostic]
publishedDiagnostics <- IO (Map NormalizedUri [Diagnostic])
forall key value. IO (Map key value)
STM.newIO
Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
positionMapping <- IO
(Map
NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping)))
forall key value. IO (Map key value)
STM.newIO
TVar (Hashed KnownTargets)
knownTargetsVar <- Hashed KnownTargets -> IO (TVar (Hashed KnownTargets))
forall a. a -> IO (TVar a)
newTVarIO (Hashed KnownTargets -> IO (TVar (Hashed KnownTargets)))
-> Hashed KnownTargets -> IO (TVar (Hashed KnownTargets))
forall a b. (a -> b) -> a -> b
$ KnownTargets -> Hashed KnownTargets
forall a. Hashable a => a -> Hashed a
hashed KnownTargets
forall k v. HashMap k v
HMap.empty
let restartShakeSession :: VFSModified -> String -> [DelayedActionInternal] -> IO ()
restartShakeSession = Recorder (WithPriority Log)
-> IdeState
-> VFSModified
-> String
-> [DelayedActionInternal]
-> IO ()
shakeRestart Recorder (WithPriority Log)
recorder IdeState
ideState
TVar (HashMap Key GetStalePersistent)
persistentKeys <- HashMap Key GetStalePersistent
-> IO (TVar (HashMap Key GetStalePersistent))
forall a. a -> IO (TVar a)
newTVarIO HashMap Key GetStalePersistent
forall k v. HashMap k v
HMap.empty
TVar (HashMap NormalizedFilePath Fingerprint)
indexPending <- HashMap NormalizedFilePath Fingerprint
-> IO (TVar (HashMap NormalizedFilePath Fingerprint))
forall a. a -> IO (TVar a)
newTVarIO HashMap NormalizedFilePath Fingerprint
forall k v. HashMap k v
HMap.empty
TVar Int
indexCompleted <- Int -> IO (TVar Int)
forall a. a -> IO (TVar a)
newTVarIO Int
0
Var (Maybe ProgressToken)
indexProgressToken <- Maybe ProgressToken -> IO (Var (Maybe ProgressToken))
forall a. a -> IO (Var a)
newVar Maybe ProgressToken
forall a. Maybe a
Nothing
let hiedbWriter :: HieDbWriter
hiedbWriter = HieDbWriter :: IndexQueue
-> TVar (HashMap NormalizedFilePath Fingerprint)
-> TVar Int
-> Var (Maybe ProgressToken)
-> HieDbWriter
HieDbWriter{TVar Int
TVar (HashMap NormalizedFilePath Fingerprint)
Var (Maybe ProgressToken)
IndexQueue
indexProgressToken :: Var (Maybe ProgressToken)
indexCompleted :: TVar Int
indexPending :: TVar (HashMap NormalizedFilePath Fingerprint)
indexQueue :: IndexQueue
$sel:indexProgressToken:HieDbWriter :: Var (Maybe ProgressToken)
$sel:indexCompleted:HieDbWriter :: TVar Int
$sel:indexPending:HieDbWriter :: TVar (HashMap NormalizedFilePath Fingerprint)
$sel:indexQueue:HieDbWriter :: IndexQueue
..}
TVar ExportsMap
exportsMap <- ExportsMap -> IO (TVar ExportsMap)
forall a. a -> IO (TVar a)
newTVarIO ExportsMap
forall a. Monoid a => a
mempty
Async ()
_ <- IO () -> IO (Async ())
forall a. IO a -> IO (Async a)
async (IO () -> IO (Async ())) -> IO () -> IO (Async ())
forall a b. (a -> b) -> a -> b
$ do
Priority -> Log -> IO ()
log Priority
Debug Log
LogCreateHieDbExportsMapStart
ExportsMap
em <- (forall a. (HieDb -> IO a) -> IO a) -> IO ExportsMap
createExportsMapHieDb forall a. (HieDb -> IO a) -> IO a
withHieDb
STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ TVar ExportsMap -> (ExportsMap -> ExportsMap) -> STM ()
forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar ExportsMap
exportsMap (ExportsMap -> ExportsMap -> ExportsMap
forall a. Semigroup a => a -> a -> a
<> ExportsMap
em)
Priority -> Log -> IO ()
log Priority
Debug (Log -> IO ()) -> Log -> IO ()
forall a b. (a -> b) -> a -> b
$ Int -> Log
LogCreateHieDbExportsMapFinish (ExportsMap -> Int
ExportsMap.size ExportsMap
em)
ProgressReporting
progress <- do
let (Seconds
before, Seconds
after) = if Bool
testing then (Seconds
0,Seconds
0.1) else (Seconds
0.1,Seconds
0.1)
if Bool
reportProgress
then Seconds
-> Seconds
-> Maybe (LanguageContextEnv Config)
-> ProgressReportingStyle
-> IO ProgressReporting
forall c.
Seconds
-> Seconds
-> Maybe (LanguageContextEnv c)
-> ProgressReportingStyle
-> IO ProgressReporting
delayedProgressReporting Seconds
before Seconds
after Maybe (LanguageContextEnv Config)
lspEnv ProgressReportingStyle
optProgressStyle
else IO ProgressReporting
noProgressReporting
ActionQueue
actionQueue <- IO ActionQueue
newQueue
let clientCapabilities :: ClientCapabilities
clientCapabilities = ClientCapabilities
-> (LanguageContextEnv Config -> ClientCapabilities)
-> Maybe (LanguageContextEnv Config)
-> ClientCapabilities
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ClientCapabilities
forall a. Default a => a
def LanguageContextEnv Config -> ClientCapabilities
forall config. LanguageContextEnv config -> ClientCapabilities
LSP.resClientCapabilities Maybe (LanguageContextEnv Config)
lspEnv
TVar (HashSet Key)
dirtyKeys <- HashSet Key -> IO (TVar (HashSet Key))
forall a. a -> IO (TVar a)
newTVarIO HashSet Key
forall a. Monoid a => a
mempty
TVar VFS
vfsVar <- VFS -> IO (TVar VFS)
forall a. a -> IO (TVar a)
newTVarIO (VFS -> IO (TVar VFS)) -> IO VFS -> IO (TVar VFS)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe (LanguageContextEnv Config) -> IO VFS
forall a. Maybe (LanguageContextEnv a) -> IO VFS
vfsSnapshot Maybe (LanguageContextEnv Config)
lspEnv
ShakeExtras -> IO ShakeExtras
forall (f :: * -> *) a. Applicative f => a -> f a
pure ShakeExtras :: Maybe (LanguageContextEnv Config)
-> Debouncer NormalizedUri
-> Logger
-> TVar (HashMap TypeRep Dynamic)
-> Values
-> STMDiagnosticStore
-> STMDiagnosticStore
-> Map NormalizedUri [Diagnostic]
-> Map
NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
-> ProgressReporting
-> IdeTesting
-> (VFSModified -> String -> [DelayedActionInternal] -> IO ())
-> IORef NameCache
-> TVar (Hashed KnownTargets)
-> TVar ExportsMap
-> ActionQueue
-> ClientCapabilities
-> (forall a. (HieDb -> IO a) -> IO a)
-> HieDbWriter
-> TVar (HashMap Key GetStalePersistent)
-> TVar VFS
-> Config
-> TVar (HashSet Key)
-> ShakeExtras
ShakeExtras{Maybe (LanguageContextEnv Config)
TVar (HashMap TypeRep Dynamic)
TVar (HashMap Key GetStalePersistent)
TVar (Hashed KnownTargets)
TVar (HashSet Key)
TVar VFS
TVar ExportsMap
IORef NameCache
Config
ClientCapabilities
Values
Map NormalizedUri [Diagnostic]
Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
STMDiagnosticStore
Debouncer NormalizedUri
Logger
ActionQueue
IdeTesting
ProgressReporting
HieDbWriter
VFSModified -> String -> [DelayedActionInternal] -> IO ()
forall a. (HieDb -> IO a) -> IO a
vfsVar :: TVar VFS
dirtyKeys :: TVar (HashSet Key)
clientCapabilities :: ClientCapabilities
actionQueue :: ActionQueue
progress :: ProgressReporting
exportsMap :: TVar ExportsMap
hiedbWriter :: HieDbWriter
persistentKeys :: TVar (HashMap Key GetStalePersistent)
restartShakeSession :: VFSModified -> String -> [DelayedActionInternal] -> IO ()
knownTargetsVar :: TVar (Hashed KnownTargets)
positionMapping :: Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
publishedDiagnostics :: Map NormalizedUri [Diagnostic]
hiddenDiagnostics :: STMDiagnosticStore
diagnostics :: STMDiagnosticStore
state :: Values
globals :: TVar (HashMap TypeRep Dynamic)
ideNc :: IORef NameCache
withHieDb :: forall a. (HieDb -> IO a) -> IO a
ideTesting :: IdeTesting
debouncer :: Debouncer NormalizedUri
logger :: Logger
defaultConfig :: Config
lspEnv :: Maybe (LanguageContextEnv Config)
$sel:dirtyKeys:ShakeExtras :: TVar (HashSet Key)
$sel:defaultConfig:ShakeExtras :: Config
$sel:vfsVar:ShakeExtras :: TVar VFS
$sel:persistentKeys:ShakeExtras :: TVar (HashMap Key GetStalePersistent)
$sel:hiedbWriter:ShakeExtras :: HieDbWriter
$sel:withHieDb:ShakeExtras :: forall a. (HieDb -> IO a) -> IO a
$sel:clientCapabilities:ShakeExtras :: ClientCapabilities
$sel:actionQueue:ShakeExtras :: ActionQueue
$sel:exportsMap:ShakeExtras :: TVar ExportsMap
$sel:knownTargetsVar:ShakeExtras :: TVar (Hashed KnownTargets)
$sel:ideNc:ShakeExtras :: IORef NameCache
$sel:restartShakeSession:ShakeExtras :: VFSModified -> String -> [DelayedActionInternal] -> IO ()
$sel:ideTesting:ShakeExtras :: IdeTesting
$sel:progress:ShakeExtras :: ProgressReporting
$sel:positionMapping:ShakeExtras :: Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
$sel:publishedDiagnostics:ShakeExtras :: Map NormalizedUri [Diagnostic]
$sel:hiddenDiagnostics:ShakeExtras :: STMDiagnosticStore
$sel:diagnostics:ShakeExtras :: STMDiagnosticStore
$sel:state:ShakeExtras :: Values
$sel:globals:ShakeExtras :: TVar (HashMap TypeRep Dynamic)
$sel:logger:ShakeExtras :: Logger
$sel:debouncer:ShakeExtras :: Debouncer NormalizedUri
$sel:lspEnv:ShakeExtras :: Maybe (LanguageContextEnv Config)
..}
ShakeDatabase
shakeDb <-
ShakeOptions -> Rules () -> IO ShakeDatabase
shakeNewDatabase
ShakeOptions
opts { shakeExtra :: Maybe Dynamic
shakeExtra = ShakeExtras -> Maybe Dynamic
forall a. Typeable a => a -> Maybe Dynamic
newShakeExtra ShakeExtras
shakeExtras }
Rules ()
rules
MVar ShakeSession
shakeSession <- IO (MVar ShakeSession)
forall a. IO (MVar a)
newEmptyMVar
ShakeDatabase -> IO (Maybe String)
shakeDatabaseProfile <- Maybe String -> IO (ShakeDatabase -> IO (Maybe String))
shakeDatabaseProfileIO Maybe String
shakeProfileDir
let ideState :: IdeState
ideState = IdeState :: ShakeDatabase
-> MVar ShakeSession
-> ShakeExtras
-> (ShakeDatabase -> IO (Maybe String))
-> IdeState
IdeState{MVar ShakeSession
ShakeDatabase
ShakeExtras
ShakeDatabase -> IO (Maybe String)
shakeDatabaseProfile :: ShakeDatabase -> IO (Maybe String)
shakeSession :: MVar ShakeSession
shakeDb :: ShakeDatabase
shakeExtras :: ShakeExtras
$sel:shakeDatabaseProfile:IdeState :: ShakeDatabase -> IO (Maybe String)
$sel:shakeSession:IdeState :: MVar ShakeSession
$sel:shakeDb:IdeState :: ShakeDatabase
$sel:shakeExtras:IdeState :: ShakeExtras
..}
IdeOptions
{ optOTMemoryProfiling :: IdeOptions -> IdeOTMemoryProfiling
optOTMemoryProfiling = IdeOTMemoryProfiling Bool
otProfilingEnabled
, ProgressReportingStyle
optProgressStyle :: IdeOptions -> ProgressReportingStyle
optProgressStyle :: ProgressReportingStyle
optProgressStyle
} <- ShakeExtras -> IO IdeOptions
getIdeOptionsIO ShakeExtras
shakeExtras
IO (Async ()) -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO (Async ()) -> IO ()) -> IO (Async ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ ShakeDatabase -> ShakeExtras -> IO (Async ())
startTelemetry ShakeDatabase
shakeDb ShakeExtras
shakeExtras
Bool -> Logger -> Values -> IO ()
startProfilingTelemetry Bool
otProfilingEnabled Logger
logger (Values -> IO ()) -> Values -> IO ()
forall a b. (a -> b) -> a -> b
$ ShakeExtras -> Values
state ShakeExtras
shakeExtras
IdeState -> IO IdeState
forall (m :: * -> *) a. Monad m => a -> m a
return IdeState
ideState
startTelemetry :: ShakeDatabase -> ShakeExtras -> IO (Async ())
startTelemetry :: ShakeDatabase -> ShakeExtras -> IO (Async ())
startTelemetry ShakeDatabase
db extras :: ShakeExtras
extras@ShakeExtras{Maybe (LanguageContextEnv Config)
TVar (HashMap TypeRep Dynamic)
TVar (HashMap Key GetStalePersistent)
TVar (Hashed KnownTargets)
TVar (HashSet Key)
TVar VFS
TVar ExportsMap
IORef NameCache
Config
ClientCapabilities
Values
Map NormalizedUri [Diagnostic]
Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
STMDiagnosticStore
Debouncer NormalizedUri
Logger
ActionQueue
IdeTesting
ProgressReporting
HieDbWriter
VFSModified -> String -> [DelayedActionInternal] -> IO ()
forall a. (HieDb -> IO a) -> IO a
dirtyKeys :: TVar (HashSet Key)
defaultConfig :: Config
vfsVar :: TVar VFS
persistentKeys :: TVar (HashMap Key GetStalePersistent)
hiedbWriter :: HieDbWriter
withHieDb :: forall a. (HieDb -> IO a) -> IO a
clientCapabilities :: ClientCapabilities
actionQueue :: ActionQueue
exportsMap :: TVar ExportsMap
knownTargetsVar :: TVar (Hashed KnownTargets)
ideNc :: IORef NameCache
restartShakeSession :: VFSModified -> String -> [DelayedActionInternal] -> IO ()
ideTesting :: IdeTesting
progress :: ProgressReporting
positionMapping :: Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
publishedDiagnostics :: Map NormalizedUri [Diagnostic]
hiddenDiagnostics :: STMDiagnosticStore
diagnostics :: STMDiagnosticStore
state :: Values
globals :: TVar (HashMap TypeRep Dynamic)
logger :: Logger
debouncer :: Debouncer NormalizedUri
lspEnv :: Maybe (LanguageContextEnv Config)
$sel:dirtyKeys:ShakeExtras :: ShakeExtras -> TVar (HashSet Key)
$sel:defaultConfig:ShakeExtras :: ShakeExtras -> Config
$sel:vfsVar:ShakeExtras :: ShakeExtras -> TVar VFS
$sel:persistentKeys:ShakeExtras :: ShakeExtras -> TVar (HashMap Key GetStalePersistent)
$sel:hiedbWriter:ShakeExtras :: ShakeExtras -> HieDbWriter
$sel:withHieDb:ShakeExtras :: ShakeExtras -> forall a. (HieDb -> IO a) -> IO a
$sel:clientCapabilities:ShakeExtras :: ShakeExtras -> ClientCapabilities
$sel:actionQueue:ShakeExtras :: ShakeExtras -> ActionQueue
$sel:exportsMap:ShakeExtras :: ShakeExtras -> TVar ExportsMap
$sel:knownTargetsVar:ShakeExtras :: ShakeExtras -> TVar (Hashed KnownTargets)
$sel:ideNc:ShakeExtras :: ShakeExtras -> IORef NameCache
$sel:restartShakeSession:ShakeExtras :: ShakeExtras
-> VFSModified -> String -> [DelayedActionInternal] -> IO ()
$sel:ideTesting:ShakeExtras :: ShakeExtras -> IdeTesting
$sel:progress:ShakeExtras :: ShakeExtras -> ProgressReporting
$sel:positionMapping:ShakeExtras :: ShakeExtras
-> Map
NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
$sel:publishedDiagnostics:ShakeExtras :: ShakeExtras -> Map NormalizedUri [Diagnostic]
$sel:hiddenDiagnostics:ShakeExtras :: ShakeExtras -> STMDiagnosticStore
$sel:diagnostics:ShakeExtras :: ShakeExtras -> STMDiagnosticStore
$sel:state:ShakeExtras :: ShakeExtras -> Values
$sel:globals:ShakeExtras :: ShakeExtras -> TVar (HashMap TypeRep Dynamic)
$sel:logger:ShakeExtras :: ShakeExtras -> Logger
$sel:debouncer:ShakeExtras :: ShakeExtras -> Debouncer NormalizedUri
$sel:lspEnv:ShakeExtras :: ShakeExtras -> Maybe (LanguageContextEnv Config)
..}
| Bool
userTracingEnabled = do
ValueObserver
countKeys <- ByteString -> IO ValueObserver
forall (m :: * -> *). MonadIO m => ByteString -> m ValueObserver
mkValueObserver ByteString
"cached keys count"
ValueObserver
countDirty <- ByteString -> IO ValueObserver
forall (m :: * -> *). MonadIO m => ByteString -> m ValueObserver
mkValueObserver ByteString
"dirty keys count"
ValueObserver
countBuilds <- ByteString -> IO ValueObserver
forall (m :: * -> *). MonadIO m => ByteString -> m ValueObserver
mkValueObserver ByteString
"builds count"
IdeOptions{IO CheckParents
optCheckParents :: IO CheckParents
optCheckParents :: IdeOptions -> IO CheckParents
optCheckParents} <- ShakeExtras -> IO IdeOptions
getIdeOptionsIO ShakeExtras
extras
CheckParents
checkParents <- IO CheckParents
optCheckParents
Seconds -> IO () -> IO (Async ())
regularly Seconds
1 (IO () -> IO (Async ())) -> IO () -> IO (Async ())
forall a b. (a -> b) -> a -> b
$ do
ValueObserver -> Int -> IO ()
forall (m :: * -> *) (a :: Additivity) (m' :: Monotonicity).
MonadIO m =>
Instrument 'Asynchronous a m' -> Int -> m ()
observe ValueObserver
countKeys (Int -> IO ())
-> ([(Key, ValueWithDiagnostics)] -> Int)
-> [(Key, ValueWithDiagnostics)]
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CheckParents -> [Key] -> Int
countRelevantKeys CheckParents
checkParents ([Key] -> Int)
-> ([(Key, ValueWithDiagnostics)] -> [Key])
-> [(Key, ValueWithDiagnostics)]
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Key, ValueWithDiagnostics) -> Key)
-> [(Key, ValueWithDiagnostics)] -> [Key]
forall a b. (a -> b) -> [a] -> [b]
map (Key, ValueWithDiagnostics) -> Key
forall a b. (a, b) -> a
fst ([(Key, ValueWithDiagnostics)] -> IO ())
-> IO [(Key, ValueWithDiagnostics)] -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (STM [(Key, ValueWithDiagnostics)]
-> IO [(Key, ValueWithDiagnostics)]
forall a. STM a -> IO a
atomically (STM [(Key, ValueWithDiagnostics)]
-> IO [(Key, ValueWithDiagnostics)])
-> (Values -> STM [(Key, ValueWithDiagnostics)])
-> Values
-> IO [(Key, ValueWithDiagnostics)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ListT STM (Key, ValueWithDiagnostics)
-> STM [(Key, ValueWithDiagnostics)]
forall (m :: * -> *) a. Monad m => ListT m a -> m [a]
ListT.toList (ListT STM (Key, ValueWithDiagnostics)
-> STM [(Key, ValueWithDiagnostics)])
-> (Values -> ListT STM (Key, ValueWithDiagnostics))
-> Values
-> STM [(Key, ValueWithDiagnostics)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Values -> ListT STM (Key, ValueWithDiagnostics)
forall key value. Map key value -> ListT STM (key, value)
STM.listT) Values
state
TVar (HashSet Key) -> IO (HashSet Key)
forall a. TVar a -> IO a
readTVarIO TVar (HashSet Key)
dirtyKeys IO (HashSet Key) -> (HashSet Key -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ValueObserver -> Int -> IO ()
forall (m :: * -> *) (a :: Additivity) (m' :: Monotonicity).
MonadIO m =>
Instrument 'Asynchronous a m' -> Int -> m ()
observe ValueObserver
countDirty (Int -> IO ()) -> (HashSet Key -> Int) -> HashSet Key -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CheckParents -> [Key] -> Int
countRelevantKeys CheckParents
checkParents ([Key] -> Int) -> (HashSet Key -> [Key]) -> HashSet Key -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashSet Key -> [Key]
forall a. HashSet a -> [a]
HSet.toList
ShakeDatabase -> IO Int
shakeGetBuildStep ShakeDatabase
db IO Int -> (Int -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ValueObserver -> Int -> IO ()
forall (m :: * -> *) (a :: Additivity) (m' :: Monotonicity).
MonadIO m =>
Instrument 'Asynchronous a m' -> Int -> m ()
observe ValueObserver
countBuilds
| Bool
otherwise = IO () -> IO (Async ())
forall a. IO a -> IO (Async a)
async (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
where
regularly :: Seconds -> IO () -> IO (Async ())
regularly :: Seconds -> IO () -> IO (Async ())
regularly Seconds
delay IO ()
act = IO () -> IO (Async ())
forall a. IO a -> IO (Async a)
async (IO () -> IO (Async ())) -> IO () -> IO (Async ())
forall a b. (a -> b) -> a -> b
$ IO () -> IO ()
forall (f :: * -> *) a b. Applicative f => f a -> f b
forever (IO ()
act IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Seconds -> IO ()
sleep Seconds
delay)
shakeSessionInit :: Recorder (WithPriority Log) -> IdeState -> IO ()
shakeSessionInit :: Recorder (WithPriority Log) -> IdeState -> IO ()
shakeSessionInit Recorder (WithPriority Log)
recorder ide :: IdeState
ide@IdeState{MVar ShakeSession
ShakeDatabase
ShakeExtras
ShakeDatabase -> IO (Maybe String)
shakeDatabaseProfile :: ShakeDatabase -> IO (Maybe String)
shakeExtras :: ShakeExtras
shakeSession :: MVar ShakeSession
shakeDb :: ShakeDatabase
$sel:shakeDatabaseProfile:IdeState :: IdeState -> ShakeDatabase -> IO (Maybe String)
$sel:shakeSession:IdeState :: IdeState -> MVar ShakeSession
$sel:shakeDb:IdeState :: IdeState -> ShakeDatabase
$sel:shakeExtras:IdeState :: IdeState -> ShakeExtras
..} = do
VFS
vfs <- Maybe (LanguageContextEnv Config) -> IO VFS
forall a. Maybe (LanguageContextEnv a) -> IO VFS
vfsSnapshot (ShakeExtras -> Maybe (LanguageContextEnv Config)
lspEnv ShakeExtras
shakeExtras)
ShakeSession
initSession <- Recorder (WithPriority Log)
-> ShakeExtras
-> VFSModified
-> ShakeDatabase
-> [DelayedActionInternal]
-> String
-> IO ShakeSession
newSession Recorder (WithPriority Log)
recorder ShakeExtras
shakeExtras (VFS -> VFSModified
VFSModified VFS
vfs) ShakeDatabase
shakeDb [] String
"shakeSessionInit"
MVar ShakeSession -> ShakeSession -> IO ()
forall a. MVar a -> a -> IO ()
putMVar MVar ShakeSession
shakeSession ShakeSession
initSession
Logger -> Text -> IO ()
logDebug (IdeState -> Logger
ideLogger IdeState
ide) Text
"Shake session initialized"
shakeShut :: IdeState -> IO ()
shakeShut :: IdeState -> IO ()
shakeShut IdeState{MVar ShakeSession
ShakeDatabase
ShakeExtras
ShakeDatabase -> IO (Maybe String)
shakeDatabaseProfile :: ShakeDatabase -> IO (Maybe String)
shakeExtras :: ShakeExtras
shakeSession :: MVar ShakeSession
shakeDb :: ShakeDatabase
$sel:shakeDatabaseProfile:IdeState :: IdeState -> ShakeDatabase -> IO (Maybe String)
$sel:shakeSession:IdeState :: IdeState -> MVar ShakeSession
$sel:shakeDb:IdeState :: IdeState -> ShakeDatabase
$sel:shakeExtras:IdeState :: IdeState -> ShakeExtras
..} = do
Maybe ShakeSession
runner <- MVar ShakeSession -> IO (Maybe ShakeSession)
forall a. MVar a -> IO (Maybe a)
tryReadMVar MVar ShakeSession
shakeSession
Maybe ShakeSession -> (ShakeSession -> IO ()) -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ Maybe ShakeSession
runner ShakeSession -> IO ()
cancelShakeSession
IO (Maybe String) -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO (Maybe String) -> IO ()) -> IO (Maybe String) -> IO ()
forall a b. (a -> b) -> a -> b
$ ShakeDatabase -> IO (Maybe String)
shakeDatabaseProfile ShakeDatabase
shakeDb
ProgressReporting -> IO ()
progressStop (ProgressReporting -> IO ()) -> ProgressReporting -> IO ()
forall a b. (a -> b) -> a -> b
$ ShakeExtras -> ProgressReporting
progress ShakeExtras
shakeExtras
withMVar' :: MVar a -> (a -> IO b) -> (b -> IO (a, c)) -> IO c
withMVar' :: MVar a -> (a -> IO b) -> (b -> IO (a, c)) -> IO c
withMVar' MVar a
var a -> IO b
unmasked b -> IO (a, c)
masked = ((forall a. IO a -> IO a) -> IO c) -> IO c
forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
uninterruptibleMask (((forall a. IO a -> IO a) -> IO c) -> IO c)
-> ((forall a. IO a -> IO a) -> IO c) -> IO c
forall a b. (a -> b) -> a -> b
$ \forall a. IO a -> IO a
restore -> do
a
a <- MVar a -> IO a
forall a. MVar a -> IO a
takeMVar MVar a
var
b
b <- IO b -> IO b
forall a. IO a -> IO a
restore (a -> IO b
unmasked a
a) IO b -> IO () -> IO b
forall a b. IO a -> IO b -> IO a
`onException` MVar a -> a -> IO ()
forall a. MVar a -> a -> IO ()
putMVar MVar a
var a
a
(a
a', c
c) <- b -> IO (a, c)
masked b
b
MVar a -> a -> IO ()
forall a. MVar a -> a -> IO ()
putMVar MVar a
var a
a'
c -> IO c
forall (f :: * -> *) a. Applicative f => a -> f a
pure c
c
mkDelayedAction :: String -> Logger.Priority -> Action a -> DelayedAction a
mkDelayedAction :: String -> Priority -> Action a -> DelayedAction a
mkDelayedAction = Maybe Unique -> String -> Priority -> Action a -> DelayedAction a
forall a.
Maybe Unique -> String -> Priority -> Action a -> DelayedAction a
DelayedAction Maybe Unique
forall a. Maybe a
Nothing
delayedAction :: DelayedAction a -> IdeAction (IO a)
delayedAction :: DelayedAction a -> IdeAction (IO a)
delayedAction DelayedAction a
a = do
ShakeExtras
extras <- IdeAction ShakeExtras
forall r (m :: * -> *). MonadReader r m => m r
ask
IO (IO a) -> IdeAction (IO a)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (IO a) -> IdeAction (IO a)) -> IO (IO a) -> IdeAction (IO a)
forall a b. (a -> b) -> a -> b
$ ShakeExtras -> DelayedAction a -> IO (IO a)
forall a. ShakeExtras -> DelayedAction a -> IO (IO a)
shakeEnqueue ShakeExtras
extras DelayedAction a
a
shakeRestart :: Recorder (WithPriority Log) -> IdeState -> VFSModified -> String -> [DelayedAction ()] -> IO ()
shakeRestart :: Recorder (WithPriority Log)
-> IdeState
-> VFSModified
-> String
-> [DelayedActionInternal]
-> IO ()
shakeRestart Recorder (WithPriority Log)
recorder IdeState{MVar ShakeSession
ShakeDatabase
ShakeExtras
ShakeDatabase -> IO (Maybe String)
shakeDatabaseProfile :: ShakeDatabase -> IO (Maybe String)
shakeExtras :: ShakeExtras
shakeSession :: MVar ShakeSession
shakeDb :: ShakeDatabase
$sel:shakeDatabaseProfile:IdeState :: IdeState -> ShakeDatabase -> IO (Maybe String)
$sel:shakeSession:IdeState :: IdeState -> MVar ShakeSession
$sel:shakeDb:IdeState :: IdeState -> ShakeDatabase
$sel:shakeExtras:IdeState :: IdeState -> ShakeExtras
..} VFSModified
vfs String
reason [DelayedActionInternal]
acts =
MVar ShakeSession
-> (ShakeSession -> IO ())
-> (() -> IO (ShakeSession, ()))
-> IO ()
forall a b c. MVar a -> (a -> IO b) -> (b -> IO (a, c)) -> IO c
withMVar'
MVar ShakeSession
shakeSession
(\ShakeSession
runner -> do
let log :: Priority -> Log -> IO ()
log = Recorder (WithPriority Log) -> Priority -> Log -> IO ()
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder
(Seconds
stopTime,()) <- IO () -> IO (Seconds, ())
forall (m :: * -> *) a. MonadIO m => m a -> m (Seconds, a)
duration (IO () -> IO (Seconds, ())) -> IO () -> IO (Seconds, ())
forall a b. (a -> b) -> a -> b
$ Seconds -> Recorder (WithPriority Log) -> IO () -> IO ()
logErrorAfter Seconds
10 Recorder (WithPriority Log)
recorder (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ ShakeSession -> IO ()
cancelShakeSession ShakeSession
runner
Maybe String
res <- ShakeDatabase -> IO (Maybe String)
shakeDatabaseProfile ShakeDatabase
shakeDb
HashSet Key
backlog <- TVar (HashSet Key) -> IO (HashSet Key)
forall a. TVar a -> IO a
readTVarIO (TVar (HashSet Key) -> IO (HashSet Key))
-> TVar (HashSet Key) -> IO (HashSet Key)
forall a b. (a -> b) -> a -> b
$ ShakeExtras -> TVar (HashSet Key)
dirtyKeys ShakeExtras
shakeExtras
[DelayedActionInternal]
queue <- String -> STM [DelayedActionInternal] -> IO [DelayedActionInternal]
forall a. String -> STM a -> IO a
atomicallyNamed String
"actionQueue - peek" (STM [DelayedActionInternal] -> IO [DelayedActionInternal])
-> STM [DelayedActionInternal] -> IO [DelayedActionInternal]
forall a b. (a -> b) -> a -> b
$ ActionQueue -> STM [DelayedActionInternal]
peekInProgress (ActionQueue -> STM [DelayedActionInternal])
-> ActionQueue -> STM [DelayedActionInternal]
forall a b. (a -> b) -> a -> b
$ ShakeExtras -> ActionQueue
actionQueue ShakeExtras
shakeExtras
Priority -> Log -> IO ()
log Priority
Debug (Log -> IO ()) -> Log -> IO ()
forall a b. (a -> b) -> a -> b
$ String
-> [DelayedActionInternal]
-> HashSet Key
-> Seconds
-> Maybe String
-> Log
LogBuildSessionRestart String
reason [DelayedActionInternal]
queue HashSet Key
backlog Seconds
stopTime Maybe String
res
let profile :: String
profile = case Maybe String
res of
Just String
fp -> String
", profile saved at " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
fp
Maybe String
_ -> String
""
let msg :: Text
msg = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"Restarting build session " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
reason' String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
queueMsg String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
keysMsg String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
abortMsg
reason' :: String
reason' = String
"due to " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
reason
queueMsg :: String
queueMsg = String
" with queue " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [String] -> String
forall a. Show a => a -> String
show ((DelayedActionInternal -> String)
-> [DelayedActionInternal] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map DelayedActionInternal -> String
forall a. DelayedAction a -> String
actionName [DelayedActionInternal]
queue)
keysMsg :: String
keysMsg = String
" for keys " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [Key] -> String
forall a. Show a => a -> String
show (HashSet Key -> [Key]
forall a. HashSet a -> [a]
HSet.toList HashSet Key
backlog) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" "
abortMsg :: String
abortMsg = String
"(aborting the previous one took " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Seconds -> String
showDuration Seconds
stopTime String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
profile String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
ShakeExtras -> Text -> IO ()
notifyTestingLogMessage ShakeExtras
shakeExtras Text
msg
)
(\() -> do
(,()) (ShakeSession -> (ShakeSession, ()))
-> IO ShakeSession -> IO (ShakeSession, ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Recorder (WithPriority Log)
-> ShakeExtras
-> VFSModified
-> ShakeDatabase
-> [DelayedActionInternal]
-> String
-> IO ShakeSession
newSession Recorder (WithPriority Log)
recorder ShakeExtras
shakeExtras VFSModified
vfs ShakeDatabase
shakeDb [DelayedActionInternal]
acts String
reason)
where
logErrorAfter :: Seconds -> Recorder (WithPriority Log) -> IO () -> IO ()
logErrorAfter :: Seconds -> Recorder (WithPriority Log) -> IO () -> IO ()
logErrorAfter Seconds
seconds Recorder (WithPriority Log)
recorder IO ()
action = (IO () -> (Async () -> IO ()) -> IO ())
-> (Async () -> IO ()) -> IO () -> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip IO () -> (Async () -> IO ()) -> IO ()
forall a b. IO a -> (Async a -> IO b) -> IO b
withAsync (IO () -> Async () -> IO ()
forall a b. a -> b -> a
const IO ()
action) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Seconds -> IO ()
sleep Seconds
seconds
Recorder (WithPriority Log) -> Priority -> Log -> IO ()
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Error (Seconds -> Log
LogBuildSessionRestartTakingTooLong Seconds
seconds)
notifyTestingLogMessage :: ShakeExtras -> T.Text -> IO ()
notifyTestingLogMessage :: ShakeExtras -> Text -> IO ()
notifyTestingLogMessage ShakeExtras
extras Text
msg = do
(IdeTesting Bool
isTestMode) <- IdeOptions -> IdeTesting
optTesting (IdeOptions -> IdeTesting) -> IO IdeOptions -> IO IdeTesting
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ShakeExtras -> IO IdeOptions
getIdeOptionsIO ShakeExtras
extras
let notif :: LogMessageParams
notif = MessageType -> Text -> LogMessageParams
LSP.LogMessageParams MessageType
LSP.MtLog Text
msg
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
isTestMode (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe (LanguageContextEnv Config) -> LspT Config IO () -> IO ()
forall (m :: * -> *) c.
Applicative m =>
Maybe (LanguageContextEnv c) -> LspT c m () -> m ()
mRunLspT (ShakeExtras -> Maybe (LanguageContextEnv Config)
lspEnv ShakeExtras
extras) (LspT Config IO () -> IO ()) -> LspT Config IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ SServerMethod 'WindowLogMessage
-> MessageParams 'WindowLogMessage -> LspT Config IO ()
forall (m :: Method 'FromServer 'Notification) (f :: * -> *)
config.
MonadLsp config f =>
SServerMethod m -> MessageParams m -> f ()
LSP.sendNotification SServerMethod 'WindowLogMessage
LSP.SWindowLogMessage MessageParams 'WindowLogMessage
LogMessageParams
notif
shakeEnqueue :: ShakeExtras -> DelayedAction a -> IO (IO a)
shakeEnqueue :: ShakeExtras -> DelayedAction a -> IO (IO a)
shakeEnqueue ShakeExtras{ActionQueue
actionQueue :: ActionQueue
$sel:actionQueue:ShakeExtras :: ShakeExtras -> ActionQueue
actionQueue, Logger
logger :: Logger
$sel:logger:ShakeExtras :: ShakeExtras -> Logger
logger} DelayedAction a
act = do
(Barrier (Either SomeException a)
b, DelayedActionInternal
dai) <- DelayedAction a
-> IO (Barrier (Either SomeException a), DelayedActionInternal)
forall a.
DelayedAction a
-> IO (Barrier (Either SomeException a), DelayedActionInternal)
instantiateDelayedAction DelayedAction a
act
String -> STM () -> IO ()
forall a. String -> STM a -> IO a
atomicallyNamed String
"actionQueue - push" (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ DelayedActionInternal -> ActionQueue -> STM ()
pushQueue DelayedActionInternal
dai ActionQueue
actionQueue
let wait' :: Barrier (Either SomeException a) -> IO (Either SomeException a)
wait' Barrier (Either SomeException a)
b =
Barrier (Either SomeException a) -> IO (Either SomeException a)
forall a. Barrier a -> IO a
waitBarrier Barrier (Either SomeException a)
b IO (Either SomeException a)
-> [Handler (Either SomeException a)]
-> IO (Either SomeException a)
forall a. IO a -> [Handler a] -> IO a
`catches`
[ (BlockedIndefinitelyOnMVar -> IO (Either SomeException a))
-> Handler (Either SomeException a)
forall a e. Exception e => (e -> IO a) -> Handler a
Handler(\BlockedIndefinitelyOnMVar
BlockedIndefinitelyOnMVar ->
String -> IO (Either SomeException a)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> IO (Either SomeException a))
-> String -> IO (Either SomeException a)
forall a b. (a -> b) -> a -> b
$ String
"internal bug: forever blocked on MVar for " String -> ShowS
forall a. Semigroup a => a -> a -> a
<>
DelayedAction a -> String
forall a. DelayedAction a -> String
actionName DelayedAction a
act)
, (AsyncCancelled -> IO (Either SomeException a))
-> Handler (Either SomeException a)
forall a e. Exception e => (e -> IO a) -> Handler a
Handler (\e :: AsyncCancelled
e@AsyncCancelled
AsyncCancelled -> do
Logger -> Priority -> Text -> IO ()
logPriority Logger
logger Priority
Debug (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ DelayedAction a -> String
forall a. DelayedAction a -> String
actionName DelayedAction a
act String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" was cancelled"
String -> STM () -> IO ()
forall a. String -> STM a -> IO a
atomicallyNamed String
"actionQueue - abort" (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ DelayedActionInternal -> ActionQueue -> STM ()
abortQueue DelayedActionInternal
dai ActionQueue
actionQueue
AsyncCancelled -> IO (Either SomeException a)
forall a e. Exception e => e -> a
throw AsyncCancelled
e)
]
IO a -> IO (IO a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Barrier (Either SomeException a) -> IO (Either SomeException a)
wait' Barrier (Either SomeException a)
b IO (Either SomeException a)
-> (Either SomeException a -> IO a) -> IO a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (SomeException -> IO a)
-> (a -> IO a) -> Either SomeException a -> IO a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either SomeException -> IO a
forall e a. Exception e => e -> IO a
throwIO a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return)
data VFSModified = VFSUnmodified | VFSModified !VFS
newSession
:: Recorder (WithPriority Log)
-> ShakeExtras
-> VFSModified
-> ShakeDatabase
-> [DelayedActionInternal]
-> String
-> IO ShakeSession
newSession :: Recorder (WithPriority Log)
-> ShakeExtras
-> VFSModified
-> ShakeDatabase
-> [DelayedActionInternal]
-> String
-> IO ShakeSession
newSession Recorder (WithPriority Log)
recorder extras :: ShakeExtras
extras@ShakeExtras{Maybe (LanguageContextEnv Config)
TVar (HashMap TypeRep Dynamic)
TVar (HashMap Key GetStalePersistent)
TVar (Hashed KnownTargets)
TVar (HashSet Key)
TVar VFS
TVar ExportsMap
IORef NameCache
Config
ClientCapabilities
Values
Map NormalizedUri [Diagnostic]
Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
STMDiagnosticStore
Debouncer NormalizedUri
Logger
ActionQueue
IdeTesting
ProgressReporting
HieDbWriter
VFSModified -> String -> [DelayedActionInternal] -> IO ()
forall a. (HieDb -> IO a) -> IO a
dirtyKeys :: TVar (HashSet Key)
defaultConfig :: Config
vfsVar :: TVar VFS
persistentKeys :: TVar (HashMap Key GetStalePersistent)
hiedbWriter :: HieDbWriter
withHieDb :: forall a. (HieDb -> IO a) -> IO a
clientCapabilities :: ClientCapabilities
actionQueue :: ActionQueue
exportsMap :: TVar ExportsMap
knownTargetsVar :: TVar (Hashed KnownTargets)
ideNc :: IORef NameCache
restartShakeSession :: VFSModified -> String -> [DelayedActionInternal] -> IO ()
ideTesting :: IdeTesting
progress :: ProgressReporting
positionMapping :: Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
publishedDiagnostics :: Map NormalizedUri [Diagnostic]
hiddenDiagnostics :: STMDiagnosticStore
diagnostics :: STMDiagnosticStore
state :: Values
globals :: TVar (HashMap TypeRep Dynamic)
logger :: Logger
debouncer :: Debouncer NormalizedUri
lspEnv :: Maybe (LanguageContextEnv Config)
$sel:dirtyKeys:ShakeExtras :: ShakeExtras -> TVar (HashSet Key)
$sel:defaultConfig:ShakeExtras :: ShakeExtras -> Config
$sel:vfsVar:ShakeExtras :: ShakeExtras -> TVar VFS
$sel:persistentKeys:ShakeExtras :: ShakeExtras -> TVar (HashMap Key GetStalePersistent)
$sel:hiedbWriter:ShakeExtras :: ShakeExtras -> HieDbWriter
$sel:withHieDb:ShakeExtras :: ShakeExtras -> forall a. (HieDb -> IO a) -> IO a
$sel:clientCapabilities:ShakeExtras :: ShakeExtras -> ClientCapabilities
$sel:actionQueue:ShakeExtras :: ShakeExtras -> ActionQueue
$sel:exportsMap:ShakeExtras :: ShakeExtras -> TVar ExportsMap
$sel:knownTargetsVar:ShakeExtras :: ShakeExtras -> TVar (Hashed KnownTargets)
$sel:ideNc:ShakeExtras :: ShakeExtras -> IORef NameCache
$sel:restartShakeSession:ShakeExtras :: ShakeExtras
-> VFSModified -> String -> [DelayedActionInternal] -> IO ()
$sel:ideTesting:ShakeExtras :: ShakeExtras -> IdeTesting
$sel:progress:ShakeExtras :: ShakeExtras -> ProgressReporting
$sel:positionMapping:ShakeExtras :: ShakeExtras
-> Map
NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
$sel:publishedDiagnostics:ShakeExtras :: ShakeExtras -> Map NormalizedUri [Diagnostic]
$sel:hiddenDiagnostics:ShakeExtras :: ShakeExtras -> STMDiagnosticStore
$sel:diagnostics:ShakeExtras :: ShakeExtras -> STMDiagnosticStore
$sel:state:ShakeExtras :: ShakeExtras -> Values
$sel:globals:ShakeExtras :: ShakeExtras -> TVar (HashMap TypeRep Dynamic)
$sel:logger:ShakeExtras :: ShakeExtras -> Logger
$sel:debouncer:ShakeExtras :: ShakeExtras -> Debouncer NormalizedUri
$sel:lspEnv:ShakeExtras :: ShakeExtras -> Maybe (LanguageContextEnv Config)
..} VFSModified
vfsMod ShakeDatabase
shakeDb [DelayedActionInternal]
acts String
reason = do
case VFSModified
vfsMod of
VFSModified
VFSUnmodified -> () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
VFSModified VFS
vfs -> STM () -> IO ()
forall a. STM a -> IO a
atomically (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ TVar VFS -> VFS -> STM ()
forall a. TVar a -> a -> STM ()
writeTVar TVar VFS
vfsVar VFS
vfs
IdeOptions{Bool
optRunSubset :: IdeOptions -> Bool
optRunSubset :: Bool
optRunSubset} <- ShakeExtras -> IO IdeOptions
getIdeOptionsIO ShakeExtras
extras
[DelayedActionInternal]
reenqueued <- String -> STM [DelayedActionInternal] -> IO [DelayedActionInternal]
forall a. String -> STM a -> IO a
atomicallyNamed String
"actionQueue - peek" (STM [DelayedActionInternal] -> IO [DelayedActionInternal])
-> STM [DelayedActionInternal] -> IO [DelayedActionInternal]
forall a b. (a -> b) -> a -> b
$ ActionQueue -> STM [DelayedActionInternal]
peekInProgress ActionQueue
actionQueue
Maybe (HashSet Key)
allPendingKeys <-
if Bool
optRunSubset
then HashSet Key -> Maybe (HashSet Key)
forall a. a -> Maybe a
Just (HashSet Key -> Maybe (HashSet Key))
-> IO (HashSet Key) -> IO (Maybe (HashSet Key))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TVar (HashSet Key) -> IO (HashSet Key)
forall a. TVar a -> IO a
readTVarIO TVar (HashSet Key)
dirtyKeys
else Maybe (HashSet Key) -> IO (Maybe (HashSet Key))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (HashSet Key)
forall a. Maybe a
Nothing
let
pumpActionThread :: SpanInFlight -> Action ()
pumpActionThread SpanInFlight
otSpan = do
DelayedActionInternal
d <- IO DelayedActionInternal -> Action DelayedActionInternal
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DelayedActionInternal -> Action DelayedActionInternal)
-> IO DelayedActionInternal -> Action DelayedActionInternal
forall a b. (a -> b) -> a -> b
$ String -> STM DelayedActionInternal -> IO DelayedActionInternal
forall a. String -> STM a -> IO a
atomicallyNamed String
"action queue - pop" (STM DelayedActionInternal -> IO DelayedActionInternal)
-> STM DelayedActionInternal -> IO DelayedActionInternal
forall a b. (a -> b) -> a -> b
$ ActionQueue -> STM DelayedActionInternal
popQueue ActionQueue
actionQueue
Action () -> (Async () -> Action ()) -> Action ()
forall a b. Action a -> (Async a -> Action b) -> Action b
actionFork (SpanInFlight -> DelayedActionInternal -> Action ()
run SpanInFlight
otSpan DelayedActionInternal
d) ((Async () -> Action ()) -> Action ())
-> (Async () -> Action ()) -> Action ()
forall a b. (a -> b) -> a -> b
$ \Async ()
_ -> SpanInFlight -> Action ()
pumpActionThread SpanInFlight
otSpan
run :: SpanInFlight -> DelayedActionInternal -> Action ()
run SpanInFlight
_otSpan DelayedActionInternal
d = do
IO Seconds
start <- IO (IO Seconds) -> Action (IO Seconds)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO (IO Seconds)
offsetTime
DelayedActionInternal -> Action ()
forall a. DelayedAction a -> Action a
getAction DelayedActionInternal
d
IO () -> Action ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Action ()) -> IO () -> Action ()
forall a b. (a -> b) -> a -> b
$ String -> STM () -> IO ()
forall a. String -> STM a -> IO a
atomicallyNamed String
"actionQueue - done" (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ DelayedActionInternal -> ActionQueue -> STM ()
doneQueue DelayedActionInternal
d ActionQueue
actionQueue
Seconds
runTime <- IO Seconds -> Action Seconds
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO Seconds
start
Recorder (WithPriority Log) -> Priority -> Log -> Action ()
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder (DelayedActionInternal -> Priority
forall a. DelayedAction a -> Priority
actionPriority DelayedActionInternal
d) (Log -> Action ()) -> Log -> Action ()
forall a b. (a -> b) -> a -> b
$ DelayedActionInternal -> Seconds -> Log
LogDelayedAction DelayedActionInternal
d Seconds
runTime
workRun :: (forall b. IO b -> IO b) -> IO (IO ())
workRun :: (forall a. IO a -> IO a) -> IO (IO ())
workRun forall a. IO a -> IO a
restore = ByteString -> (SpanInFlight -> IO (IO ())) -> IO (IO ())
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
ByteString -> (SpanInFlight -> m a) -> m a
withSpan ByteString
"Shake session" ((SpanInFlight -> IO (IO ())) -> IO (IO ()))
-> (SpanInFlight -> IO (IO ())) -> IO (IO ())
forall a b. (a -> b) -> a -> b
$ \SpanInFlight
otSpan -> do
SpanInFlight -> ByteString -> ByteString -> IO ()
forall (m :: * -> *).
MonadIO m =>
SpanInFlight -> ByteString -> ByteString -> m ()
setTag SpanInFlight
otSpan ByteString
"reason" (String -> ByteString
forall a. IsString a => String -> a
fromString String
reason)
SpanInFlight -> ByteString -> ByteString -> IO ()
forall (m :: * -> *).
MonadIO m =>
SpanInFlight -> ByteString -> ByteString -> m ()
setTag SpanInFlight
otSpan ByteString
"queue" (String -> ByteString
forall a. IsString a => String -> a
fromString (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (DelayedActionInternal -> String)
-> [DelayedActionInternal] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map DelayedActionInternal -> String
forall a. DelayedAction a -> String
actionName [DelayedActionInternal]
reenqueued)
Maybe (HashSet Key) -> (HashSet Key -> IO ()) -> IO ()
forall (m :: * -> *) a.
Applicative m =>
Maybe a -> (a -> m ()) -> m ()
whenJust Maybe (HashSet Key)
allPendingKeys ((HashSet Key -> IO ()) -> IO ())
-> (HashSet Key -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \HashSet Key
kk -> SpanInFlight -> ByteString -> ByteString -> IO ()
forall (m :: * -> *).
MonadIO m =>
SpanInFlight -> ByteString -> ByteString -> m ()
setTag SpanInFlight
otSpan ByteString
"keys" (String -> ByteString
BS8.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (Key -> String) -> [Key] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Key -> String
forall a. Show a => a -> String
show ([Key] -> [String]) -> [Key] -> [String]
forall a b. (a -> b) -> a -> b
$ HashSet Key -> [Key]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList HashSet Key
kk)
let keysActs :: [Action ()]
keysActs = SpanInFlight -> Action ()
pumpActionThread SpanInFlight
otSpan Action () -> [Action ()] -> [Action ()]
forall a. a -> [a] -> [a]
: (DelayedActionInternal -> Action ())
-> [DelayedActionInternal] -> [Action ()]
forall a b. (a -> b) -> [a] -> [b]
map (SpanInFlight -> DelayedActionInternal -> Action ()
run SpanInFlight
otSpan) ([DelayedActionInternal]
reenqueued [DelayedActionInternal]
-> [DelayedActionInternal] -> [DelayedActionInternal]
forall a. [a] -> [a] -> [a]
++ [DelayedActionInternal]
acts)
Either SomeException [()]
res <- forall a.
Exception SomeException =>
IO a -> IO (Either SomeException a)
forall e a. Exception e => IO a -> IO (Either e a)
try @SomeException (IO [()] -> IO (Either SomeException [()]))
-> IO [()] -> IO (Either SomeException [()])
forall a b. (a -> b) -> a -> b
$
IO [()] -> IO [()]
forall a. IO a -> IO a
restore (IO [()] -> IO [()]) -> IO [()] -> IO [()]
forall a b. (a -> b) -> a -> b
$ Maybe [Key] -> ShakeDatabase -> [Action ()] -> IO [()]
forall a. Maybe [Key] -> ShakeDatabase -> [Action a] -> IO [a]
shakeRunDatabaseForKeys (HashSet Key -> [Key]
forall a. HashSet a -> [a]
HSet.toList (HashSet Key -> [Key]) -> Maybe (HashSet Key) -> Maybe [Key]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (HashSet Key)
allPendingKeys) ShakeDatabase
shakeDb [Action ()]
keysActs
let res' :: String
res' = case Either SomeException [()]
res of
Left SomeException
e -> String
"exception: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> SomeException -> String
forall e. Exception e => e -> String
displayException SomeException
e
Right [()]
_ -> String
"completed"
let msg :: Text
msg = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"Finishing build session(" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
res' String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
IO () -> IO (IO ())
forall (m :: * -> *) a. Monad m => a -> m a
return (IO () -> IO (IO ())) -> IO () -> IO (IO ())
forall a b. (a -> b) -> a -> b
$ do
let exception :: Maybe SomeException
exception =
case Either SomeException [()]
res of
Left SomeException
e -> SomeException -> Maybe SomeException
forall a. a -> Maybe a
Just SomeException
e
Either SomeException [()]
_ -> Maybe SomeException
forall a. Maybe a
Nothing
Recorder (WithPriority Log) -> Priority -> Log -> IO ()
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Debug (Log -> IO ()) -> Log -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe SomeException -> Log
LogBuildSessionFinish Maybe SomeException
exception
ShakeExtras -> Text -> IO ()
notifyTestingLogMessage ShakeExtras
extras Text
msg
Async (IO ())
workThread <- ((forall a. IO a -> IO a) -> IO (IO ())) -> IO (Async (IO ()))
forall a. ((forall a. IO a -> IO a) -> IO a) -> IO (Async a)
asyncWithUnmask (forall a. IO a -> IO a) -> IO (IO ())
workRun
Async ()
_ <- IO () -> IO (Async ())
forall a. IO a -> IO (Async a)
async (IO () -> IO (Async ())) -> IO () -> IO (Async ())
forall a b. (a -> b) -> a -> b
$ IO (IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (IO (IO ()) -> IO ()) -> IO (IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ Async (IO ()) -> IO (IO ())
forall a. Async a -> IO a
wait Async (IO ())
workThread
let cancelShakeSession :: IO ()
cancelShakeSession :: IO ()
cancelShakeSession = Async (IO ()) -> IO ()
forall a. Async a -> IO ()
cancel Async (IO ())
workThread
ShakeSession -> IO ShakeSession
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ShakeSession :: IO () -> ShakeSession
ShakeSession{IO ()
cancelShakeSession :: IO ()
$sel:cancelShakeSession:ShakeSession :: IO ()
..})
instantiateDelayedAction
:: DelayedAction a
-> IO (Barrier (Either SomeException a), DelayedActionInternal)
instantiateDelayedAction :: DelayedAction a
-> IO (Barrier (Either SomeException a), DelayedActionInternal)
instantiateDelayedAction (DelayedAction Maybe Unique
_ String
s Priority
p Action a
a) = do
Unique
u <- IO Unique
newUnique
Barrier (Either SomeException a)
b <- IO (Barrier (Either SomeException a))
forall a. IO (Barrier a)
newBarrier
let a' :: Action ()
a' = do
Bool
alreadyDone <- IO Bool -> Action Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> Action Bool) -> IO Bool -> Action Bool
forall a b. (a -> b) -> a -> b
$ Maybe (Either SomeException a) -> Bool
forall a. Maybe a -> Bool
isJust (Maybe (Either SomeException a) -> Bool)
-> IO (Maybe (Either SomeException a)) -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Barrier (Either SomeException a)
-> IO (Maybe (Either SomeException a))
forall a. Barrier a -> IO (Maybe a)
waitBarrierMaybe Barrier (Either SomeException a)
b
Bool -> Action () -> Action ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
alreadyDone (Action () -> Action ()) -> Action () -> Action ()
forall a b. (a -> b) -> a -> b
$ do
Either SomeException a
x <- Action (Either SomeException a)
-> (SomeException -> Action (Either SomeException a))
-> Action (Either SomeException a)
forall e a. Exception e => Action a -> (e -> Action a) -> Action a
actionCatch @SomeException (a -> Either SomeException a
forall a b. b -> Either a b
Right (a -> Either SomeException a)
-> Action a -> Action (Either SomeException a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Action a
a) (Either SomeException a -> Action (Either SomeException a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either SomeException a -> Action (Either SomeException a))
-> (SomeException -> Either SomeException a)
-> SomeException
-> Action (Either SomeException a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> Either SomeException a
forall a b. a -> Either a b
Left)
IO () -> Action ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Action ()) -> IO () -> Action ()
forall a b. (a -> b) -> a -> b
$ IO (Either SomeException ()) -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO (Either SomeException ()) -> IO ())
-> IO (Either SomeException ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ forall a.
Exception SomeException =>
IO a -> IO (Either SomeException a)
forall e a. Exception e => IO a -> IO (Either e a)
try @SomeException (IO () -> IO (Either SomeException ()))
-> IO () -> IO (Either SomeException ())
forall a b. (a -> b) -> a -> b
$ Barrier (Either SomeException a) -> Either SomeException a -> IO ()
forall a. HasCallStack => Barrier a -> a -> IO ()
signalBarrier Barrier (Either SomeException a)
b Either SomeException a
x
d' :: DelayedActionInternal
d' = Maybe Unique
-> String -> Priority -> Action () -> DelayedActionInternal
forall a.
Maybe Unique -> String -> Priority -> Action a -> DelayedAction a
DelayedAction (Unique -> Maybe Unique
forall a. a -> Maybe a
Just Unique
u) String
s Priority
p Action ()
a'
(Barrier (Either SomeException a), DelayedActionInternal)
-> IO (Barrier (Either SomeException a), DelayedActionInternal)
forall (m :: * -> *) a. Monad m => a -> m a
return (Barrier (Either SomeException a)
b, DelayedActionInternal
d')
getDiagnostics :: IdeState -> STM [FileDiagnostic]
getDiagnostics :: IdeState -> STM [FileDiagnostic]
getDiagnostics IdeState{$sel:shakeExtras:IdeState :: IdeState -> ShakeExtras
shakeExtras = ShakeExtras{STMDiagnosticStore
diagnostics :: STMDiagnosticStore
$sel:diagnostics:ShakeExtras :: ShakeExtras -> STMDiagnosticStore
diagnostics}} = do
STMDiagnosticStore -> STM [FileDiagnostic]
getAllDiagnostics STMDiagnosticStore
diagnostics
getHiddenDiagnostics :: IdeState -> STM [FileDiagnostic]
getHiddenDiagnostics :: IdeState -> STM [FileDiagnostic]
getHiddenDiagnostics IdeState{$sel:shakeExtras:IdeState :: IdeState -> ShakeExtras
shakeExtras = ShakeExtras{STMDiagnosticStore
hiddenDiagnostics :: STMDiagnosticStore
$sel:hiddenDiagnostics:ShakeExtras :: ShakeExtras -> STMDiagnosticStore
hiddenDiagnostics}} = do
STMDiagnosticStore -> STM [FileDiagnostic]
getAllDiagnostics STMDiagnosticStore
hiddenDiagnostics
garbageCollectDirtyKeys :: Action [Key]
garbageCollectDirtyKeys :: Action [Key]
garbageCollectDirtyKeys = do
IdeOptions{IO CheckParents
optCheckParents :: IO CheckParents
optCheckParents :: IdeOptions -> IO CheckParents
optCheckParents} <- Action IdeOptions
getIdeOptions
CheckParents
checkParents <- IO CheckParents -> Action CheckParents
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO CheckParents
optCheckParents
Int -> CheckParents -> Action [Key]
garbageCollectDirtyKeysOlderThan Int
0 CheckParents
checkParents
garbageCollectDirtyKeysOlderThan :: Int -> CheckParents -> Action [Key]
garbageCollectDirtyKeysOlderThan :: Int -> CheckParents -> Action [Key]
garbageCollectDirtyKeysOlderThan Int
maxAge CheckParents
checkParents = ByteString -> Action [Key] -> Action [Key]
forall (f :: * -> *) a.
(MonadMask f, MonadIO f, Show a) =>
ByteString -> f [a] -> f [a]
otTracedGarbageCollection ByteString
"dirty GC" (Action [Key] -> Action [Key]) -> Action [Key] -> Action [Key]
forall a b. (a -> b) -> a -> b
$ do
[(Key, Int)]
dirtySet <- Action [(Key, Int)]
getDirtySet
String -> Int -> CheckParents -> [(Key, Int)] -> Action [Key]
garbageCollectKeys String
"dirty GC" Int
maxAge CheckParents
checkParents [(Key, Int)]
dirtySet
garbageCollectKeys :: String -> Int -> CheckParents -> [(Key, Int)] -> Action [Key]
garbageCollectKeys :: String -> Int -> CheckParents -> [(Key, Int)] -> Action [Key]
garbageCollectKeys String
label Int
maxAge CheckParents
checkParents [(Key, Int)]
agedKeys = do
IO Seconds
start <- IO (IO Seconds) -> Action (IO Seconds)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO (IO Seconds)
offsetTime
ShakeExtras{Values
state :: Values
$sel:state:ShakeExtras :: ShakeExtras -> Values
state, TVar (HashSet Key)
dirtyKeys :: TVar (HashSet Key)
$sel:dirtyKeys:ShakeExtras :: ShakeExtras -> TVar (HashSet Key)
dirtyKeys, Maybe (LanguageContextEnv Config)
lspEnv :: Maybe (LanguageContextEnv Config)
$sel:lspEnv:ShakeExtras :: ShakeExtras -> Maybe (LanguageContextEnv Config)
lspEnv, Logger
logger :: Logger
$sel:logger:ShakeExtras :: ShakeExtras -> Logger
logger, IdeTesting
ideTesting :: IdeTesting
$sel:ideTesting:ShakeExtras :: ShakeExtras -> IdeTesting
ideTesting} <- Action ShakeExtras
getShakeExtras
(Int
n::Int, [Key]
garbage) <- IO (Int, [Key]) -> Action (Int, [Key])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int, [Key]) -> Action (Int, [Key]))
-> IO (Int, [Key]) -> Action (Int, [Key])
forall a b. (a -> b) -> a -> b
$
((Int, [Key]) -> (Key, Int) -> IO (Int, [Key]))
-> (Int, [Key]) -> [(Key, Int)] -> IO (Int, [Key])
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (TVar (HashSet Key)
-> Values -> (Int, [Key]) -> (Key, Int) -> IO (Int, [Key])
removeDirtyKey TVar (HashSet Key)
dirtyKeys Values
state) (Int
0,[]) [(Key, Int)]
agedKeys
Seconds
t <- IO Seconds -> Action Seconds
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO Seconds
start
Bool -> Action () -> Action ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
nInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>Int
0) (Action () -> Action ()) -> Action () -> Action ()
forall a b. (a -> b) -> a -> b
$ IO () -> Action ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Action ()) -> IO () -> Action ()
forall a b. (a -> b) -> a -> b
$ do
Logger -> Text -> IO ()
logDebug Logger
logger (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$
String
label String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" of " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> String
forall a. Show a => a -> String
show Int
n String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" keys (took " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Seconds -> String
showDuration Seconds
t String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
")"
Bool -> Action () -> Action ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (IdeTesting -> Bool
coerce IdeTesting
ideTesting) (Action () -> Action ()) -> Action () -> Action ()
forall a b. (a -> b) -> a -> b
$ IO () -> Action ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Action ()) -> IO () -> Action ()
forall a b. (a -> b) -> a -> b
$ Maybe (LanguageContextEnv Config) -> LspT Config IO () -> IO ()
forall (m :: * -> *) c.
Applicative m =>
Maybe (LanguageContextEnv c) -> LspT c m () -> m ()
mRunLspT Maybe (LanguageContextEnv Config)
lspEnv (LspT Config IO () -> IO ()) -> LspT Config IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
SServerMethod 'CustomMethod
-> MessageParams 'CustomMethod -> LspT Config IO ()
forall (m :: Method 'FromServer 'Notification) (f :: * -> *)
config.
MonadLsp config f =>
SServerMethod m -> MessageParams m -> f ()
LSP.sendNotification (Text -> SServerMethod 'CustomMethod
forall (f :: From) (t :: MethodType). Text -> SMethod 'CustomMethod
SCustomMethod Text
"ghcide/GC")
([String] -> Value
forall a. ToJSON a => a -> Value
toJSON ([String] -> Value) -> [String] -> Value
forall a b. (a -> b) -> a -> b
$ (Key -> Maybe String) -> [Key] -> [String]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (((TypeRep, NormalizedFilePath) -> String)
-> Maybe (TypeRep, NormalizedFilePath) -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (TypeRep, NormalizedFilePath) -> String
showKey (Maybe (TypeRep, NormalizedFilePath) -> Maybe String)
-> (Key -> Maybe (TypeRep, NormalizedFilePath))
-> Key
-> Maybe String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> Maybe (TypeRep, NormalizedFilePath)
fromKeyType) [Key]
garbage)
[Key] -> Action [Key]
forall (m :: * -> *) a. Monad m => a -> m a
return [Key]
garbage
where
showKey :: (TypeRep, NormalizedFilePath) -> String
showKey = Q TypeRep -> String
forall a. Show a => a -> String
show (Q TypeRep -> String)
-> ((TypeRep, NormalizedFilePath) -> Q TypeRep)
-> (TypeRep, NormalizedFilePath)
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TypeRep, NormalizedFilePath) -> Q TypeRep
forall k. (k, NormalizedFilePath) -> Q k
Q
removeDirtyKey :: TVar (HashSet Key)
-> Values -> (Int, [Key]) -> (Key, Int) -> IO (Int, [Key])
removeDirtyKey TVar (HashSet Key)
dk Values
values st :: (Int, [Key])
st@(!Int
counter, [Key]
keys) (Key
k, Int
age)
| Int
age Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
maxAge
, Just (TypeRep
kt,NormalizedFilePath
_) <- Key -> Maybe (TypeRep, NormalizedFilePath)
fromKeyType Key
k
, Bool -> Bool
not(TypeRep
kt TypeRep -> HashSet TypeRep -> Bool
forall a. (Eq a, Hashable a) => a -> HashSet a -> Bool
`HSet.member` CheckParents -> HashSet TypeRep
preservedKeys CheckParents
checkParents)
= String -> STM (Int, [Key]) -> IO (Int, [Key])
forall a. String -> STM a -> IO a
atomicallyNamed String
"GC" (STM (Int, [Key]) -> IO (Int, [Key]))
-> STM (Int, [Key]) -> IO (Int, [Key])
forall a b. (a -> b) -> a -> b
$ do
Bool
gotIt <- Focus ValueWithDiagnostics STM Bool -> Key -> Values -> STM Bool
forall key value result.
(Eq key, Hashable key) =>
Focus value STM result -> key -> Map key value -> STM result
STM.focus (Focus ValueWithDiagnostics STM Bool
forall (m :: * -> *) a. Monad m => Focus a m Bool
Focus.member Focus ValueWithDiagnostics STM Bool
-> Focus ValueWithDiagnostics STM ()
-> Focus ValueWithDiagnostics STM Bool
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Focus ValueWithDiagnostics STM ()
forall (m :: * -> *) a. Monad m => Focus a m ()
Focus.delete) Key
k Values
values
Bool -> STM () -> STM ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
gotIt (STM () -> STM ()) -> STM () -> STM ()
forall a b. (a -> b) -> a -> b
$
TVar (HashSet Key) -> (HashSet Key -> HashSet Key) -> STM ()
forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar (HashSet Key)
dk (Key -> HashSet Key -> HashSet Key
forall a. (Eq a, Hashable a) => a -> HashSet a -> HashSet a
HSet.insert Key
k)
(Int, [Key]) -> STM (Int, [Key])
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int, [Key]) -> STM (Int, [Key]))
-> (Int, [Key]) -> STM (Int, [Key])
forall a b. (a -> b) -> a -> b
$ if Bool
gotIt then (Int
counterInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1, Key
kKey -> [Key] -> [Key]
forall a. a -> [a] -> [a]
:[Key]
keys) else (Int, [Key])
st
| Bool
otherwise = (Int, [Key]) -> IO (Int, [Key])
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int, [Key])
st
countRelevantKeys :: CheckParents -> [Key] -> Int
countRelevantKeys :: CheckParents -> [Key] -> Int
countRelevantKeys CheckParents
checkParents =
[Key] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
Prelude.length ([Key] -> Int) -> ([Key] -> [Key]) -> [Key] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> Bool) -> [Key] -> [Key]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool
-> ((TypeRep, NormalizedFilePath) -> Bool)
-> Maybe (TypeRep, NormalizedFilePath)
-> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Bool -> Bool
not (Bool -> Bool)
-> ((TypeRep, NormalizedFilePath) -> Bool)
-> (TypeRep, NormalizedFilePath)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TypeRep -> HashSet TypeRep -> Bool
forall a. (Eq a, Hashable a) => a -> HashSet a -> Bool
`HSet.member` CheckParents -> HashSet TypeRep
preservedKeys CheckParents
checkParents) (TypeRep -> Bool)
-> ((TypeRep, NormalizedFilePath) -> TypeRep)
-> (TypeRep, NormalizedFilePath)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TypeRep, NormalizedFilePath) -> TypeRep
forall a b. (a, b) -> a
fst) (Maybe (TypeRep, NormalizedFilePath) -> Bool)
-> (Key -> Maybe (TypeRep, NormalizedFilePath)) -> Key -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> Maybe (TypeRep, NormalizedFilePath)
fromKeyType)
preservedKeys :: CheckParents -> HashSet TypeRep
preservedKeys :: CheckParents -> HashSet TypeRep
preservedKeys CheckParents
checkParents = [TypeRep] -> HashSet TypeRep
forall a. (Eq a, Hashable a) => [a] -> HashSet a
HSet.fromList ([TypeRep] -> HashSet TypeRep) -> [TypeRep] -> HashSet TypeRep
forall a b. (a -> b) -> a -> b
$
[ GetFileExists -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf GetFileExists
GetFileExists
, GetModificationTime -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf GetModificationTime
GetModificationTime
, IsFileOfInterest -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf IsFileOfInterest
IsFileOfInterest
, GhcSessionIO -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf GhcSessionIO
GhcSessionIO
, GetClientSettings -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf GetClientSettings
GetClientSettings
, AddWatchedFile -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf AddWatchedFile
AddWatchedFile
, GetKnownTargets -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf GetKnownTargets
GetKnownTargets
]
[TypeRep] -> [TypeRep] -> [TypeRep]
forall a. [a] -> [a] -> [a]
++ [[TypeRep]] -> [TypeRep]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ [ GetModSummary -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf GetModSummary
GetModSummary
, GetModSummaryWithoutTimestamps -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf GetModSummaryWithoutTimestamps
GetModSummaryWithoutTimestamps
, GetLocatedImports -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf GetLocatedImports
GetLocatedImports
]
| CheckParents
checkParents CheckParents -> CheckParents -> Bool
forall a. Eq a => a -> a -> Bool
/= CheckParents
NeverCheck
]
define
:: IdeRule k v
=> Recorder (WithPriority Log) -> (k -> NormalizedFilePath -> Action (IdeResult v)) -> Rules ()
define :: Recorder (WithPriority Log)
-> (k -> NormalizedFilePath -> Action (IdeResult v)) -> Rules ()
define Recorder (WithPriority Log)
recorder k -> NormalizedFilePath -> Action (IdeResult v)
op = Recorder (WithPriority Log) -> RuleBody k v -> Rules ()
forall k v.
IdeRule k v =>
Recorder (WithPriority Log) -> RuleBody k v -> Rules ()
defineEarlyCutoff Recorder (WithPriority Log)
recorder (RuleBody k v -> Rules ()) -> RuleBody k v -> Rules ()
forall a b. (a -> b) -> a -> b
$ (k -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult v))
-> RuleBody k v
forall k v.
(k -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult v))
-> RuleBody k v
Rule ((k
-> NormalizedFilePath -> Action (Maybe ByteString, IdeResult v))
-> RuleBody k v)
-> (k
-> NormalizedFilePath -> Action (Maybe ByteString, IdeResult v))
-> RuleBody k v
forall a b. (a -> b) -> a -> b
$ \k
k NormalizedFilePath
v -> (Maybe ByteString
forall a. Maybe a
Nothing,) (IdeResult v -> (Maybe ByteString, IdeResult v))
-> Action (IdeResult v) -> Action (Maybe ByteString, IdeResult v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> k -> NormalizedFilePath -> Action (IdeResult v)
op k
k NormalizedFilePath
v
defineNoDiagnostics
:: IdeRule k v
=> Recorder (WithPriority Log) -> (k -> NormalizedFilePath -> Action (Maybe v)) -> Rules ()
defineNoDiagnostics :: Recorder (WithPriority Log)
-> (k -> NormalizedFilePath -> Action (Maybe v)) -> Rules ()
defineNoDiagnostics Recorder (WithPriority Log)
recorder k -> NormalizedFilePath -> Action (Maybe v)
op = Recorder (WithPriority Log) -> RuleBody k v -> Rules ()
forall k v.
IdeRule k v =>
Recorder (WithPriority Log) -> RuleBody k v -> Rules ()
defineEarlyCutoff Recorder (WithPriority Log)
recorder (RuleBody k v -> Rules ()) -> RuleBody k v -> Rules ()
forall a b. (a -> b) -> a -> b
$ (k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v))
-> RuleBody k v
forall k v.
(k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v))
-> RuleBody k v
RuleNoDiagnostics ((k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v))
-> RuleBody k v)
-> (k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v))
-> RuleBody k v
forall a b. (a -> b) -> a -> b
$ \k
k NormalizedFilePath
v -> (Maybe ByteString
forall a. Maybe a
Nothing,) (Maybe v -> (Maybe ByteString, Maybe v))
-> Action (Maybe v) -> Action (Maybe ByteString, Maybe v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> k -> NormalizedFilePath -> Action (Maybe v)
op k
k NormalizedFilePath
v
use :: IdeRule k v
=> k -> NormalizedFilePath -> Action (Maybe v)
use :: k -> NormalizedFilePath -> Action (Maybe v)
use k
key NormalizedFilePath
file = [Maybe v] -> Maybe v
forall a. [a] -> a
head ([Maybe v] -> Maybe v) -> Action [Maybe v] -> Action (Maybe v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> k -> [NormalizedFilePath] -> Action [Maybe v]
forall k v.
IdeRule k v =>
k -> [NormalizedFilePath] -> Action [Maybe v]
uses k
key [NormalizedFilePath
file]
useWithStale :: IdeRule k v
=> k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping))
useWithStale :: k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping))
useWithStale k
key NormalizedFilePath
file = [Maybe (v, PositionMapping)] -> Maybe (v, PositionMapping)
forall a. [a] -> a
head ([Maybe (v, PositionMapping)] -> Maybe (v, PositionMapping))
-> Action [Maybe (v, PositionMapping)]
-> Action (Maybe (v, PositionMapping))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> k -> [NormalizedFilePath] -> Action [Maybe (v, PositionMapping)]
forall k v.
IdeRule k v =>
k -> [NormalizedFilePath] -> Action [Maybe (v, PositionMapping)]
usesWithStale k
key [NormalizedFilePath
file]
useWithStale_ :: IdeRule k v
=> k -> NormalizedFilePath -> Action (v, PositionMapping)
useWithStale_ :: k -> NormalizedFilePath -> Action (v, PositionMapping)
useWithStale_ k
key NormalizedFilePath
file = [(v, PositionMapping)] -> (v, PositionMapping)
forall a. [a] -> a
head ([(v, PositionMapping)] -> (v, PositionMapping))
-> Action [(v, PositionMapping)] -> Action (v, PositionMapping)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> k -> [NormalizedFilePath] -> Action [(v, PositionMapping)]
forall k v.
IdeRule k v =>
k -> [NormalizedFilePath] -> Action [(v, PositionMapping)]
usesWithStale_ k
key [NormalizedFilePath
file]
usesWithStale_ :: IdeRule k v => k -> [NormalizedFilePath] -> Action [(v, PositionMapping)]
usesWithStale_ :: k -> [NormalizedFilePath] -> Action [(v, PositionMapping)]
usesWithStale_ k
key [NormalizedFilePath]
files = do
[Maybe (v, PositionMapping)]
res <- k -> [NormalizedFilePath] -> Action [Maybe (v, PositionMapping)]
forall k v.
IdeRule k v =>
k -> [NormalizedFilePath] -> Action [Maybe (v, PositionMapping)]
usesWithStale k
key [NormalizedFilePath]
files
case [Maybe (v, PositionMapping)] -> Maybe [(v, PositionMapping)]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Maybe (v, PositionMapping)]
res of
Maybe [(v, PositionMapping)]
Nothing -> IO [(v, PositionMapping)] -> Action [(v, PositionMapping)]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [(v, PositionMapping)] -> Action [(v, PositionMapping)])
-> IO [(v, PositionMapping)] -> Action [(v, PositionMapping)]
forall a b. (a -> b) -> a -> b
$ BadDependency -> IO [(v, PositionMapping)]
forall e a. Exception e => e -> IO a
throwIO (BadDependency -> IO [(v, PositionMapping)])
-> BadDependency -> IO [(v, PositionMapping)]
forall a b. (a -> b) -> a -> b
$ String -> BadDependency
BadDependency (k -> String
forall a. Show a => a -> String
show k
key)
Just [(v, PositionMapping)]
v -> [(v, PositionMapping)] -> Action [(v, PositionMapping)]
forall (m :: * -> *) a. Monad m => a -> m a
return [(v, PositionMapping)]
v
newtype IdeAction a = IdeAction { IdeAction a -> ReaderT ShakeExtras IO a
runIdeActionT :: (ReaderT ShakeExtras IO) a }
deriving newtype (MonadReader ShakeExtras, Monad IdeAction
Monad IdeAction
-> (forall a. IO a -> IdeAction a) -> MonadIO IdeAction
IO a -> IdeAction a
forall a. IO a -> IdeAction a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
liftIO :: IO a -> IdeAction a
$cliftIO :: forall a. IO a -> IdeAction a
$cp1MonadIO :: Monad IdeAction
MonadIO, a -> IdeAction b -> IdeAction a
(a -> b) -> IdeAction a -> IdeAction b
(forall a b. (a -> b) -> IdeAction a -> IdeAction b)
-> (forall a b. a -> IdeAction b -> IdeAction a)
-> Functor IdeAction
forall a b. a -> IdeAction b -> IdeAction a
forall a b. (a -> b) -> IdeAction a -> IdeAction b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> IdeAction b -> IdeAction a
$c<$ :: forall a b. a -> IdeAction b -> IdeAction a
fmap :: (a -> b) -> IdeAction a -> IdeAction b
$cfmap :: forall a b. (a -> b) -> IdeAction a -> IdeAction b
Functor, Functor IdeAction
a -> IdeAction a
Functor IdeAction
-> (forall a. a -> IdeAction a)
-> (forall a b. IdeAction (a -> b) -> IdeAction a -> IdeAction b)
-> (forall a b c.
(a -> b -> c) -> IdeAction a -> IdeAction b -> IdeAction c)
-> (forall a b. IdeAction a -> IdeAction b -> IdeAction b)
-> (forall a b. IdeAction a -> IdeAction b -> IdeAction a)
-> Applicative IdeAction
IdeAction a -> IdeAction b -> IdeAction b
IdeAction a -> IdeAction b -> IdeAction a
IdeAction (a -> b) -> IdeAction a -> IdeAction b
(a -> b -> c) -> IdeAction a -> IdeAction b -> IdeAction c
forall a. a -> IdeAction a
forall a b. IdeAction a -> IdeAction b -> IdeAction a
forall a b. IdeAction a -> IdeAction b -> IdeAction b
forall a b. IdeAction (a -> b) -> IdeAction a -> IdeAction b
forall a b c.
(a -> b -> c) -> IdeAction a -> IdeAction b -> IdeAction c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: IdeAction a -> IdeAction b -> IdeAction a
$c<* :: forall a b. IdeAction a -> IdeAction b -> IdeAction a
*> :: IdeAction a -> IdeAction b -> IdeAction b
$c*> :: forall a b. IdeAction a -> IdeAction b -> IdeAction b
liftA2 :: (a -> b -> c) -> IdeAction a -> IdeAction b -> IdeAction c
$cliftA2 :: forall a b c.
(a -> b -> c) -> IdeAction a -> IdeAction b -> IdeAction c
<*> :: IdeAction (a -> b) -> IdeAction a -> IdeAction b
$c<*> :: forall a b. IdeAction (a -> b) -> IdeAction a -> IdeAction b
pure :: a -> IdeAction a
$cpure :: forall a. a -> IdeAction a
$cp1Applicative :: Functor IdeAction
Applicative, Applicative IdeAction
a -> IdeAction a
Applicative IdeAction
-> (forall a b. IdeAction a -> (a -> IdeAction b) -> IdeAction b)
-> (forall a b. IdeAction a -> IdeAction b -> IdeAction b)
-> (forall a. a -> IdeAction a)
-> Monad IdeAction
IdeAction a -> (a -> IdeAction b) -> IdeAction b
IdeAction a -> IdeAction b -> IdeAction b
forall a. a -> IdeAction a
forall a b. IdeAction a -> IdeAction b -> IdeAction b
forall a b. IdeAction a -> (a -> IdeAction b) -> IdeAction b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> IdeAction a
$creturn :: forall a. a -> IdeAction a
>> :: IdeAction a -> IdeAction b -> IdeAction b
$c>> :: forall a b. IdeAction a -> IdeAction b -> IdeAction b
>>= :: IdeAction a -> (a -> IdeAction b) -> IdeAction b
$c>>= :: forall a b. IdeAction a -> (a -> IdeAction b) -> IdeAction b
$cp1Monad :: Applicative IdeAction
Monad)
runIdeAction :: String -> ShakeExtras -> IdeAction a -> IO a
runIdeAction :: String -> ShakeExtras -> IdeAction a -> IO a
runIdeAction String
_herald ShakeExtras
s IdeAction a
i = ReaderT ShakeExtras IO a -> ShakeExtras -> IO a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (IdeAction a -> ReaderT ShakeExtras IO a
forall a. IdeAction a -> ReaderT ShakeExtras IO a
runIdeActionT IdeAction a
i) ShakeExtras
s
askShake :: IdeAction ShakeExtras
askShake :: IdeAction ShakeExtras
askShake = IdeAction ShakeExtras
forall r (m :: * -> *). MonadReader r m => m r
ask
mkUpdater :: IORef NameCache -> NameCacheUpdater
mkUpdater :: IORef NameCache -> NameCacheUpdater
mkUpdater IORef NameCache
ref = (forall c. (NameCache -> (NameCache, c)) -> IO c)
-> NameCacheUpdater
NCU (IORef NameCache -> (NameCache -> (NameCache, c)) -> IO c
forall c. IORef NameCache -> (NameCache -> (NameCache, c)) -> IO c
upNameCache IORef NameCache
ref)
data FastResult a = FastResult { FastResult a -> Maybe (a, PositionMapping)
stale :: Maybe (a,PositionMapping), FastResult a -> IO (Maybe a)
uptoDate :: IO (Maybe a) }
useWithStaleFast :: IdeRule k v => k -> NormalizedFilePath -> IdeAction (Maybe (v, PositionMapping))
useWithStaleFast :: k -> NormalizedFilePath -> IdeAction (Maybe (v, PositionMapping))
useWithStaleFast k
key NormalizedFilePath
file = FastResult v -> Maybe (v, PositionMapping)
forall a. FastResult a -> Maybe (a, PositionMapping)
stale (FastResult v -> Maybe (v, PositionMapping))
-> IdeAction (FastResult v)
-> IdeAction (Maybe (v, PositionMapping))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> k -> NormalizedFilePath -> IdeAction (FastResult v)
forall k v.
IdeRule k v =>
k -> NormalizedFilePath -> IdeAction (FastResult v)
useWithStaleFast' k
key NormalizedFilePath
file
useWithStaleFast' :: IdeRule k v => k -> NormalizedFilePath -> IdeAction (FastResult v)
useWithStaleFast' :: k -> NormalizedFilePath -> IdeAction (FastResult v)
useWithStaleFast' k
key NormalizedFilePath
file = do
IO (Maybe v)
wait <- DelayedAction (Maybe v) -> IdeAction (IO (Maybe v))
forall a. DelayedAction a -> IdeAction (IO a)
delayedAction (DelayedAction (Maybe v) -> IdeAction (IO (Maybe v)))
-> DelayedAction (Maybe v) -> IdeAction (IO (Maybe v))
forall a b. (a -> b) -> a -> b
$ String -> Priority -> Action (Maybe v) -> DelayedAction (Maybe v)
forall a. String -> Priority -> Action a -> DelayedAction a
mkDelayedAction (String
"C:" String -> ShowS
forall a. [a] -> [a] -> [a]
++ k -> String
forall a. Show a => a -> String
show k
key String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
":" String -> ShowS
forall a. [a] -> [a] -> [a]
++ NormalizedFilePath -> String
fromNormalizedFilePath NormalizedFilePath
file) Priority
Debug (Action (Maybe v) -> DelayedAction (Maybe v))
-> Action (Maybe v) -> DelayedAction (Maybe v)
forall a b. (a -> b) -> a -> b
$ k -> NormalizedFilePath -> Action (Maybe v)
forall k v.
IdeRule k v =>
k -> NormalizedFilePath -> Action (Maybe v)
use k
key NormalizedFilePath
file
s :: ShakeExtras
s@ShakeExtras{Values
state :: Values
$sel:state:ShakeExtras :: ShakeExtras -> Values
state} <- IdeAction ShakeExtras
askShake
Maybe (Value v, Vector FileDiagnostic)
r <- IO (Maybe (Value v, Vector FileDiagnostic))
-> IdeAction (Maybe (Value v, Vector FileDiagnostic))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe (Value v, Vector FileDiagnostic))
-> IdeAction (Maybe (Value v, Vector FileDiagnostic)))
-> IO (Maybe (Value v, Vector FileDiagnostic))
-> IdeAction (Maybe (Value v, Vector FileDiagnostic))
forall a b. (a -> b) -> a -> b
$ String
-> STM (Maybe (Value v, Vector FileDiagnostic))
-> IO (Maybe (Value v, Vector FileDiagnostic))
forall a. String -> STM a -> IO a
atomicallyNamed String
"useStateFast" (STM (Maybe (Value v, Vector FileDiagnostic))
-> IO (Maybe (Value v, Vector FileDiagnostic)))
-> STM (Maybe (Value v, Vector FileDiagnostic))
-> IO (Maybe (Value v, Vector FileDiagnostic))
forall a b. (a -> b) -> a -> b
$ Values
-> k
-> NormalizedFilePath
-> STM (Maybe (Value v, Vector FileDiagnostic))
forall k v.
IdeRule k v =>
Values
-> k
-> NormalizedFilePath
-> STM (Maybe (Value v, Vector FileDiagnostic))
getValues Values
state k
key NormalizedFilePath
file
IO (FastResult v) -> IdeAction (FastResult v)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (FastResult v) -> IdeAction (FastResult v))
-> IO (FastResult v) -> IdeAction (FastResult v)
forall a b. (a -> b) -> a -> b
$ case Maybe (Value v, Vector FileDiagnostic)
r of
Maybe (Value v, Vector FileDiagnostic)
Nothing -> do
Maybe (v, PositionMapping)
res <- ShakeExtras
-> k -> NormalizedFilePath -> IO (Maybe (v, PositionMapping))
forall k v.
IdeRule k v =>
ShakeExtras
-> k -> NormalizedFilePath -> IO (Maybe (v, PositionMapping))
lastValueIO ShakeExtras
s k
key NormalizedFilePath
file
case Maybe (v, PositionMapping)
res of
Maybe (v, PositionMapping)
Nothing -> do
Maybe v
a <- IO (Maybe v)
wait
FastResult v -> IO (FastResult v)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FastResult v -> IO (FastResult v))
-> FastResult v -> IO (FastResult v)
forall a b. (a -> b) -> a -> b
$ Maybe (v, PositionMapping) -> IO (Maybe v) -> FastResult v
forall a.
Maybe (a, PositionMapping) -> IO (Maybe a) -> FastResult a
FastResult ((,PositionMapping
zeroMapping) (v -> (v, PositionMapping))
-> Maybe v -> Maybe (v, PositionMapping)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe v
a) (Maybe v -> IO (Maybe v)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe v
a)
Just (v, PositionMapping)
_ -> FastResult v -> IO (FastResult v)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FastResult v -> IO (FastResult v))
-> FastResult v -> IO (FastResult v)
forall a b. (a -> b) -> a -> b
$ Maybe (v, PositionMapping) -> IO (Maybe v) -> FastResult v
forall a.
Maybe (a, PositionMapping) -> IO (Maybe a) -> FastResult a
FastResult Maybe (v, PositionMapping)
res IO (Maybe v)
wait
Just (Value v, Vector FileDiagnostic)
_ -> do
Maybe (v, PositionMapping)
res <- ShakeExtras
-> k -> NormalizedFilePath -> IO (Maybe (v, PositionMapping))
forall k v.
IdeRule k v =>
ShakeExtras
-> k -> NormalizedFilePath -> IO (Maybe (v, PositionMapping))
lastValueIO ShakeExtras
s k
key NormalizedFilePath
file
FastResult v -> IO (FastResult v)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FastResult v -> IO (FastResult v))
-> FastResult v -> IO (FastResult v)
forall a b. (a -> b) -> a -> b
$ Maybe (v, PositionMapping) -> IO (Maybe v) -> FastResult v
forall a.
Maybe (a, PositionMapping) -> IO (Maybe a) -> FastResult a
FastResult Maybe (v, PositionMapping)
res IO (Maybe v)
wait
useNoFile :: IdeRule k v => k -> Action (Maybe v)
useNoFile :: k -> Action (Maybe v)
useNoFile k
key = k -> NormalizedFilePath -> Action (Maybe v)
forall k v.
IdeRule k v =>
k -> NormalizedFilePath -> Action (Maybe v)
use k
key NormalizedFilePath
emptyFilePath
use_ :: IdeRule k v => k -> NormalizedFilePath -> Action v
use_ :: k -> NormalizedFilePath -> Action v
use_ k
key NormalizedFilePath
file = [v] -> v
forall a. [a] -> a
head ([v] -> v) -> Action [v] -> Action v
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> k -> [NormalizedFilePath] -> Action [v]
forall k v. IdeRule k v => k -> [NormalizedFilePath] -> Action [v]
uses_ k
key [NormalizedFilePath
file]
useNoFile_ :: IdeRule k v => k -> Action v
useNoFile_ :: k -> Action v
useNoFile_ k
key = k -> NormalizedFilePath -> Action v
forall k v. IdeRule k v => k -> NormalizedFilePath -> Action v
use_ k
key NormalizedFilePath
emptyFilePath
uses_ :: IdeRule k v => k -> [NormalizedFilePath] -> Action [v]
uses_ :: k -> [NormalizedFilePath] -> Action [v]
uses_ k
key [NormalizedFilePath]
files = do
[Maybe v]
res <- k -> [NormalizedFilePath] -> Action [Maybe v]
forall k v.
IdeRule k v =>
k -> [NormalizedFilePath] -> Action [Maybe v]
uses k
key [NormalizedFilePath]
files
case [Maybe v] -> Maybe [v]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Maybe v]
res of
Maybe [v]
Nothing -> IO [v] -> Action [v]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [v] -> Action [v]) -> IO [v] -> Action [v]
forall a b. (a -> b) -> a -> b
$ BadDependency -> IO [v]
forall e a. Exception e => e -> IO a
throwIO (BadDependency -> IO [v]) -> BadDependency -> IO [v]
forall a b. (a -> b) -> a -> b
$ String -> BadDependency
BadDependency (k -> String
forall a. Show a => a -> String
show k
key)
Just [v]
v -> [v] -> Action [v]
forall (m :: * -> *) a. Monad m => a -> m a
return [v]
v
uses :: IdeRule k v
=> k -> [NormalizedFilePath] -> Action [Maybe v]
uses :: k -> [NormalizedFilePath] -> Action [Maybe v]
uses k
key [NormalizedFilePath]
files = (A v -> Maybe v) -> [A v] -> [Maybe v]
forall a b. (a -> b) -> [a] -> [b]
map (\(A Value v
value) -> Value v -> Maybe v
forall v. Value v -> Maybe v
currentValue Value v
value) ([A v] -> [Maybe v]) -> Action [A v] -> Action [Maybe v]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Q k] -> Action [A v]
forall key value.
(RuleResult key ~ value, ShakeValue key, Typeable value) =>
[key] -> Action [value]
apply ((NormalizedFilePath -> Q k) -> [NormalizedFilePath] -> [Q k]
forall a b. (a -> b) -> [a] -> [b]
map ((k, NormalizedFilePath) -> Q k
forall k. (k, NormalizedFilePath) -> Q k
Q ((k, NormalizedFilePath) -> Q k)
-> (NormalizedFilePath -> (k, NormalizedFilePath))
-> NormalizedFilePath
-> Q k
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (k
key,)) [NormalizedFilePath]
files)
usesWithStale :: IdeRule k v
=> k -> [NormalizedFilePath] -> Action [Maybe (v, PositionMapping)]
usesWithStale :: k -> [NormalizedFilePath] -> Action [Maybe (v, PositionMapping)]
usesWithStale k
key [NormalizedFilePath]
files = do
[A v]
_ <- [Q k] -> Action [A v]
forall key value.
(RuleResult key ~ value, ShakeValue key, Typeable value) =>
[key] -> Action [value]
apply ((NormalizedFilePath -> Q k) -> [NormalizedFilePath] -> [Q k]
forall a b. (a -> b) -> [a] -> [b]
map ((k, NormalizedFilePath) -> Q k
forall k. (k, NormalizedFilePath) -> Q k
Q ((k, NormalizedFilePath) -> Q k)
-> (NormalizedFilePath -> (k, NormalizedFilePath))
-> NormalizedFilePath
-> Q k
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (k
key,)) [NormalizedFilePath]
files)
(NormalizedFilePath -> Action (Maybe (v, PositionMapping)))
-> [NormalizedFilePath] -> Action [Maybe (v, PositionMapping)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping))
forall k v.
IdeRule k v =>
k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping))
lastValue k
key) [NormalizedFilePath]
files
useWithoutDependency :: IdeRule k v
=> k -> NormalizedFilePath -> Action (Maybe v)
useWithoutDependency :: k -> NormalizedFilePath -> Action (Maybe v)
useWithoutDependency k
key NormalizedFilePath
file =
(\[A Value v
value] -> Value v -> Maybe v
forall v. Value v -> Maybe v
currentValue Value v
value) ([A v] -> Maybe v) -> Action [A v] -> Action (Maybe v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Q k] -> Action [A v]
forall key value.
(RuleResult key ~ value, ShakeValue key, Typeable value) =>
[key] -> Action [value]
applyWithoutDependency [(k, NormalizedFilePath) -> Q k
forall k. (k, NormalizedFilePath) -> Q k
Q (k
key, NormalizedFilePath
file)]
data RuleBody k v
= Rule (k -> NormalizedFilePath -> Action (Maybe BS.ByteString, IdeResult v))
| RuleNoDiagnostics (k -> NormalizedFilePath -> Action (Maybe BS.ByteString, Maybe v))
| RuleWithCustomNewnessCheck
{ RuleBody k v -> ByteString -> ByteString -> Bool
newnessCheck :: BS.ByteString -> BS.ByteString -> Bool
, RuleBody k v
-> k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v)
build :: k -> NormalizedFilePath -> Action (Maybe BS.ByteString, Maybe v)
}
| RuleWithOldValue (k -> NormalizedFilePath -> Value v -> Action (Maybe BS.ByteString, IdeResult v))
defineEarlyCutoff
:: IdeRule k v
=> Recorder (WithPriority Log)
-> RuleBody k v
-> Rules ()
defineEarlyCutoff :: Recorder (WithPriority Log) -> RuleBody k v -> Rules ()
defineEarlyCutoff Recorder (WithPriority Log)
recorder (Rule k -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult v)
op) = (Q k -> Maybe ByteString -> RunMode -> Action (RunResult (A v)))
-> Rules ()
forall key value.
(RuleResult key ~ value, Typeable key, Hashable key, Eq key,
Typeable value) =>
(key -> Maybe ByteString -> RunMode -> Action (RunResult value))
-> Rules ()
addRule ((Q k -> Maybe ByteString -> RunMode -> Action (RunResult (A v)))
-> Rules ())
-> (Q k -> Maybe ByteString -> RunMode -> Action (RunResult (A v)))
-> Rules ()
forall a b. (a -> b) -> a -> b
$ \(Q (k
key, NormalizedFilePath
file)) (Maybe ByteString
old :: Maybe BS.ByteString) RunMode
mode -> k
-> NormalizedFilePath
-> RunMode
-> (A v -> String)
-> (([FileDiagnostic] -> Action ()) -> Action (RunResult (A v)))
-> Action (RunResult (A v))
forall k a.
Show k =>
k
-> NormalizedFilePath
-> RunMode
-> (a -> String)
-> (([FileDiagnostic] -> Action ()) -> Action (RunResult a))
-> Action (RunResult a)
otTracedAction k
key NormalizedFilePath
file RunMode
mode A v -> String
forall v. A v -> String
traceA ((([FileDiagnostic] -> Action ()) -> Action (RunResult (A v)))
-> Action (RunResult (A v)))
-> (([FileDiagnostic] -> Action ()) -> Action (RunResult (A v)))
-> Action (RunResult (A v))
forall a b. (a -> b) -> a -> b
$ \[FileDiagnostic] -> Action ()
traceDiagnostics -> do
ShakeExtras
extras <- Action ShakeExtras
getShakeExtras
let diagnostics :: TextDocumentVersion -> [FileDiagnostic] -> Action ()
diagnostics TextDocumentVersion
ver [FileDiagnostic]
diags = do
[FileDiagnostic] -> Action ()
traceDiagnostics [FileDiagnostic]
diags
Recorder (WithPriority Log)
-> NormalizedFilePath
-> TextDocumentVersion
-> Key
-> ShakeExtras
-> [(ShowDiagnostic, Diagnostic)]
-> Action ()
forall (m :: * -> *).
MonadIO m =>
Recorder (WithPriority Log)
-> NormalizedFilePath
-> TextDocumentVersion
-> Key
-> ShakeExtras
-> [(ShowDiagnostic, Diagnostic)]
-> m ()
updateFileDiagnostics Recorder (WithPriority Log)
recorder NormalizedFilePath
file TextDocumentVersion
ver (k -> Key
forall a. (Typeable a, Eq a, Hashable a, Show a) => a -> Key
Key k
key) ShakeExtras
extras ([(ShowDiagnostic, Diagnostic)] -> Action ())
-> ([FileDiagnostic] -> [(ShowDiagnostic, Diagnostic)])
-> [FileDiagnostic]
-> Action ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FileDiagnostic -> (ShowDiagnostic, Diagnostic))
-> [FileDiagnostic] -> [(ShowDiagnostic, Diagnostic)]
forall a b. (a -> b) -> [a] -> [b]
map (\(NormalizedFilePath
_,ShowDiagnostic
y,Diagnostic
z) -> (ShowDiagnostic
y,Diagnostic
z)) ([FileDiagnostic] -> Action ()) -> [FileDiagnostic] -> Action ()
forall a b. (a -> b) -> a -> b
$ [FileDiagnostic]
diags
(TextDocumentVersion -> [FileDiagnostic] -> Action ())
-> (ByteString -> ByteString -> Bool)
-> k
-> NormalizedFilePath
-> Maybe ByteString
-> RunMode
-> (Value v -> Action (Maybe ByteString, IdeResult v))
-> Action (RunResult (A (RuleResult k)))
forall k v.
IdeRule k v =>
(TextDocumentVersion -> [FileDiagnostic] -> Action ())
-> (ByteString -> ByteString -> Bool)
-> k
-> NormalizedFilePath
-> Maybe ByteString
-> RunMode
-> (Value v -> Action (Maybe ByteString, IdeResult v))
-> Action (RunResult (A (RuleResult k)))
defineEarlyCutoff' TextDocumentVersion -> [FileDiagnostic] -> Action ()
diagnostics ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
(==) k
key NormalizedFilePath
file Maybe ByteString
old RunMode
mode ((Value v -> Action (Maybe ByteString, IdeResult v))
-> Action (RunResult (A (RuleResult k))))
-> (Value v -> Action (Maybe ByteString, IdeResult v))
-> Action (RunResult (A (RuleResult k)))
forall a b. (a -> b) -> a -> b
$ Action (Maybe ByteString, IdeResult v)
-> Value v -> Action (Maybe ByteString, IdeResult v)
forall a b. a -> b -> a
const (Action (Maybe ByteString, IdeResult v)
-> Value v -> Action (Maybe ByteString, IdeResult v))
-> Action (Maybe ByteString, IdeResult v)
-> Value v
-> Action (Maybe ByteString, IdeResult v)
forall a b. (a -> b) -> a -> b
$ k -> NormalizedFilePath -> Action (Maybe ByteString, IdeResult v)
op k
key NormalizedFilePath
file
defineEarlyCutoff Recorder (WithPriority Log)
recorder (RuleNoDiagnostics k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v)
op) = (Q k -> Maybe ByteString -> RunMode -> Action (RunResult (A v)))
-> Rules ()
forall key value.
(RuleResult key ~ value, Typeable key, Hashable key, Eq key,
Typeable value) =>
(key -> Maybe ByteString -> RunMode -> Action (RunResult value))
-> Rules ()
addRule ((Q k -> Maybe ByteString -> RunMode -> Action (RunResult (A v)))
-> Rules ())
-> (Q k -> Maybe ByteString -> RunMode -> Action (RunResult (A v)))
-> Rules ()
forall a b. (a -> b) -> a -> b
$ \(Q (k
key, NormalizedFilePath
file)) (Maybe ByteString
old :: Maybe BS.ByteString) RunMode
mode -> k
-> NormalizedFilePath
-> RunMode
-> (A v -> String)
-> (([FileDiagnostic] -> Action ()) -> Action (RunResult (A v)))
-> Action (RunResult (A v))
forall k a.
Show k =>
k
-> NormalizedFilePath
-> RunMode
-> (a -> String)
-> (([FileDiagnostic] -> Action ()) -> Action (RunResult a))
-> Action (RunResult a)
otTracedAction k
key NormalizedFilePath
file RunMode
mode A v -> String
forall v. A v -> String
traceA ((([FileDiagnostic] -> Action ()) -> Action (RunResult (A v)))
-> Action (RunResult (A v)))
-> (([FileDiagnostic] -> Action ()) -> Action (RunResult (A v)))
-> Action (RunResult (A v))
forall a b. (a -> b) -> a -> b
$ \[FileDiagnostic] -> Action ()
traceDiagnostics -> do
let diagnostics :: TextDocumentVersion -> [FileDiagnostic] -> Action ()
diagnostics TextDocumentVersion
_ver [FileDiagnostic]
diags = do
[FileDiagnostic] -> Action ()
traceDiagnostics [FileDiagnostic]
diags
(FileDiagnostic -> Action ()) -> [FileDiagnostic] -> Action ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Recorder (WithPriority Log) -> Priority -> Log -> Action ()
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Warning (Log -> Action ())
-> (FileDiagnostic -> Log) -> FileDiagnostic -> Action ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileDiagnostic -> Log
LogDefineEarlyCutoffRuleNoDiagHasDiag) [FileDiagnostic]
diags
(TextDocumentVersion -> [FileDiagnostic] -> Action ())
-> (ByteString -> ByteString -> Bool)
-> k
-> NormalizedFilePath
-> Maybe ByteString
-> RunMode
-> (Value v -> Action (Maybe ByteString, IdeResult v))
-> Action (RunResult (A (RuleResult k)))
forall k v.
IdeRule k v =>
(TextDocumentVersion -> [FileDiagnostic] -> Action ())
-> (ByteString -> ByteString -> Bool)
-> k
-> NormalizedFilePath
-> Maybe ByteString
-> RunMode
-> (Value v -> Action (Maybe ByteString, IdeResult v))
-> Action (RunResult (A (RuleResult k)))
defineEarlyCutoff' TextDocumentVersion -> [FileDiagnostic] -> Action ()
diagnostics ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
(==) k
key NormalizedFilePath
file Maybe ByteString
old RunMode
mode ((Value v -> Action (Maybe ByteString, IdeResult v))
-> Action (RunResult (A (RuleResult k))))
-> (Value v -> Action (Maybe ByteString, IdeResult v))
-> Action (RunResult (A (RuleResult k)))
forall a b. (a -> b) -> a -> b
$ Action (Maybe ByteString, IdeResult v)
-> Value v -> Action (Maybe ByteString, IdeResult v)
forall a b. a -> b -> a
const (Action (Maybe ByteString, IdeResult v)
-> Value v -> Action (Maybe ByteString, IdeResult v))
-> Action (Maybe ByteString, IdeResult v)
-> Value v
-> Action (Maybe ByteString, IdeResult v)
forall a b. (a -> b) -> a -> b
$ (Maybe v -> IdeResult v)
-> (Maybe ByteString, Maybe v) -> (Maybe ByteString, IdeResult v)
forall b b' a. (b -> b') -> (a, b) -> (a, b')
second ([FileDiagnostic]
forall a. Monoid a => a
mempty,) ((Maybe ByteString, Maybe v) -> (Maybe ByteString, IdeResult v))
-> Action (Maybe ByteString, Maybe v)
-> Action (Maybe ByteString, IdeResult v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v)
op k
key NormalizedFilePath
file
defineEarlyCutoff Recorder (WithPriority Log)
recorder RuleWithCustomNewnessCheck{k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v)
ByteString -> ByteString -> Bool
build :: k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v)
newnessCheck :: ByteString -> ByteString -> Bool
$sel:build:Rule :: forall k v.
RuleBody k v
-> k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v)
$sel:newnessCheck:Rule :: forall k v. RuleBody k v -> ByteString -> ByteString -> Bool
..} =
(Q k -> Maybe ByteString -> RunMode -> Action (RunResult (A v)))
-> Rules ()
forall key value.
(RuleResult key ~ value, Typeable key, Hashable key, Eq key,
Typeable value) =>
(key -> Maybe ByteString -> RunMode -> Action (RunResult value))
-> Rules ()
addRule ((Q k -> Maybe ByteString -> RunMode -> Action (RunResult (A v)))
-> Rules ())
-> (Q k -> Maybe ByteString -> RunMode -> Action (RunResult (A v)))
-> Rules ()
forall a b. (a -> b) -> a -> b
$ \(Q (k
key, NormalizedFilePath
file)) (Maybe ByteString
old :: Maybe BS.ByteString) RunMode
mode ->
k
-> NormalizedFilePath
-> RunMode
-> (A v -> String)
-> (([FileDiagnostic] -> Action ()) -> Action (RunResult (A v)))
-> Action (RunResult (A v))
forall k a.
Show k =>
k
-> NormalizedFilePath
-> RunMode
-> (a -> String)
-> (([FileDiagnostic] -> Action ()) -> Action (RunResult a))
-> Action (RunResult a)
otTracedAction k
key NormalizedFilePath
file RunMode
mode A v -> String
forall v. A v -> String
traceA ((([FileDiagnostic] -> Action ()) -> Action (RunResult (A v)))
-> Action (RunResult (A v)))
-> (([FileDiagnostic] -> Action ()) -> Action (RunResult (A v)))
-> Action (RunResult (A v))
forall a b. (a -> b) -> a -> b
$ \ [FileDiagnostic] -> Action ()
traceDiagnostics -> do
let diagnostics :: TextDocumentVersion -> [FileDiagnostic] -> Action ()
diagnostics TextDocumentVersion
_ver [FileDiagnostic]
diags = do
[FileDiagnostic] -> Action ()
traceDiagnostics [FileDiagnostic]
diags
(FileDiagnostic -> Action ()) -> [FileDiagnostic] -> Action ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Recorder (WithPriority Log) -> Priority -> Log -> Action ()
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Warning (Log -> Action ())
-> (FileDiagnostic -> Log) -> FileDiagnostic -> Action ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileDiagnostic -> Log
LogDefineEarlyCutoffRuleCustomNewnessHasDiag) [FileDiagnostic]
diags
(TextDocumentVersion -> [FileDiagnostic] -> Action ())
-> (ByteString -> ByteString -> Bool)
-> k
-> NormalizedFilePath
-> Maybe ByteString
-> RunMode
-> (Value v -> Action (Maybe ByteString, IdeResult v))
-> Action (RunResult (A (RuleResult k)))
forall k v.
IdeRule k v =>
(TextDocumentVersion -> [FileDiagnostic] -> Action ())
-> (ByteString -> ByteString -> Bool)
-> k
-> NormalizedFilePath
-> Maybe ByteString
-> RunMode
-> (Value v -> Action (Maybe ByteString, IdeResult v))
-> Action (RunResult (A (RuleResult k)))
defineEarlyCutoff' TextDocumentVersion -> [FileDiagnostic] -> Action ()
diagnostics ByteString -> ByteString -> Bool
newnessCheck k
key NormalizedFilePath
file Maybe ByteString
old RunMode
mode ((Value v -> Action (Maybe ByteString, IdeResult v))
-> Action (RunResult (A (RuleResult k))))
-> (Value v -> Action (Maybe ByteString, IdeResult v))
-> Action (RunResult (A (RuleResult k)))
forall a b. (a -> b) -> a -> b
$
Action (Maybe ByteString, IdeResult v)
-> Value v -> Action (Maybe ByteString, IdeResult v)
forall a b. a -> b -> a
const (Action (Maybe ByteString, IdeResult v)
-> Value v -> Action (Maybe ByteString, IdeResult v))
-> Action (Maybe ByteString, IdeResult v)
-> Value v
-> Action (Maybe ByteString, IdeResult v)
forall a b. (a -> b) -> a -> b
$ (Maybe v -> IdeResult v)
-> (Maybe ByteString, Maybe v) -> (Maybe ByteString, IdeResult v)
forall b b' a. (b -> b') -> (a, b) -> (a, b')
second ([FileDiagnostic]
forall a. Monoid a => a
mempty,) ((Maybe ByteString, Maybe v) -> (Maybe ByteString, IdeResult v))
-> Action (Maybe ByteString, Maybe v)
-> Action (Maybe ByteString, IdeResult v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v)
build k
key NormalizedFilePath
file
defineEarlyCutoff Recorder (WithPriority Log)
recorder (RuleWithOldValue k
-> NormalizedFilePath
-> Value v
-> Action (Maybe ByteString, IdeResult v)
op) = (Q k -> Maybe ByteString -> RunMode -> Action (RunResult (A v)))
-> Rules ()
forall key value.
(RuleResult key ~ value, Typeable key, Hashable key, Eq key,
Typeable value) =>
(key -> Maybe ByteString -> RunMode -> Action (RunResult value))
-> Rules ()
addRule ((Q k -> Maybe ByteString -> RunMode -> Action (RunResult (A v)))
-> Rules ())
-> (Q k -> Maybe ByteString -> RunMode -> Action (RunResult (A v)))
-> Rules ()
forall a b. (a -> b) -> a -> b
$ \(Q (k
key, NormalizedFilePath
file)) (Maybe ByteString
old :: Maybe BS.ByteString) RunMode
mode -> k
-> NormalizedFilePath
-> RunMode
-> (A v -> String)
-> (([FileDiagnostic] -> Action ()) -> Action (RunResult (A v)))
-> Action (RunResult (A v))
forall k a.
Show k =>
k
-> NormalizedFilePath
-> RunMode
-> (a -> String)
-> (([FileDiagnostic] -> Action ()) -> Action (RunResult a))
-> Action (RunResult a)
otTracedAction k
key NormalizedFilePath
file RunMode
mode A v -> String
forall v. A v -> String
traceA ((([FileDiagnostic] -> Action ()) -> Action (RunResult (A v)))
-> Action (RunResult (A v)))
-> (([FileDiagnostic] -> Action ()) -> Action (RunResult (A v)))
-> Action (RunResult (A v))
forall a b. (a -> b) -> a -> b
$ \[FileDiagnostic] -> Action ()
traceDiagnostics -> do
ShakeExtras
extras <- Action ShakeExtras
getShakeExtras
let diagnostics :: TextDocumentVersion -> [FileDiagnostic] -> Action ()
diagnostics TextDocumentVersion
ver [FileDiagnostic]
diags = do
[FileDiagnostic] -> Action ()
traceDiagnostics [FileDiagnostic]
diags
Recorder (WithPriority Log)
-> NormalizedFilePath
-> TextDocumentVersion
-> Key
-> ShakeExtras
-> [(ShowDiagnostic, Diagnostic)]
-> Action ()
forall (m :: * -> *).
MonadIO m =>
Recorder (WithPriority Log)
-> NormalizedFilePath
-> TextDocumentVersion
-> Key
-> ShakeExtras
-> [(ShowDiagnostic, Diagnostic)]
-> m ()
updateFileDiagnostics Recorder (WithPriority Log)
recorder NormalizedFilePath
file TextDocumentVersion
ver (k -> Key
forall a. (Typeable a, Eq a, Hashable a, Show a) => a -> Key
Key k
key) ShakeExtras
extras ([(ShowDiagnostic, Diagnostic)] -> Action ())
-> ([FileDiagnostic] -> [(ShowDiagnostic, Diagnostic)])
-> [FileDiagnostic]
-> Action ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FileDiagnostic -> (ShowDiagnostic, Diagnostic))
-> [FileDiagnostic] -> [(ShowDiagnostic, Diagnostic)]
forall a b. (a -> b) -> [a] -> [b]
map (\(NormalizedFilePath
_,ShowDiagnostic
y,Diagnostic
z) -> (ShowDiagnostic
y,Diagnostic
z)) ([FileDiagnostic] -> Action ()) -> [FileDiagnostic] -> Action ()
forall a b. (a -> b) -> a -> b
$ [FileDiagnostic]
diags
(TextDocumentVersion -> [FileDiagnostic] -> Action ())
-> (ByteString -> ByteString -> Bool)
-> k
-> NormalizedFilePath
-> Maybe ByteString
-> RunMode
-> (Value v -> Action (Maybe ByteString, IdeResult v))
-> Action (RunResult (A (RuleResult k)))
forall k v.
IdeRule k v =>
(TextDocumentVersion -> [FileDiagnostic] -> Action ())
-> (ByteString -> ByteString -> Bool)
-> k
-> NormalizedFilePath
-> Maybe ByteString
-> RunMode
-> (Value v -> Action (Maybe ByteString, IdeResult v))
-> Action (RunResult (A (RuleResult k)))
defineEarlyCutoff' TextDocumentVersion -> [FileDiagnostic] -> Action ()
diagnostics ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
(==) k
key NormalizedFilePath
file Maybe ByteString
old RunMode
mode ((Value v -> Action (Maybe ByteString, IdeResult v))
-> Action (RunResult (A (RuleResult k))))
-> (Value v -> Action (Maybe ByteString, IdeResult v))
-> Action (RunResult (A (RuleResult k)))
forall a b. (a -> b) -> a -> b
$ k
-> NormalizedFilePath
-> Value v
-> Action (Maybe ByteString, IdeResult v)
op k
key NormalizedFilePath
file
defineNoFile :: IdeRule k v => Recorder (WithPriority Log) -> (k -> Action v) -> Rules ()
defineNoFile :: Recorder (WithPriority Log) -> (k -> Action v) -> Rules ()
defineNoFile Recorder (WithPriority Log)
recorder k -> Action v
f = Recorder (WithPriority Log)
-> (k -> NormalizedFilePath -> Action (Maybe v)) -> Rules ()
forall k v.
IdeRule k v =>
Recorder (WithPriority Log)
-> (k -> NormalizedFilePath -> Action (Maybe v)) -> Rules ()
defineNoDiagnostics Recorder (WithPriority Log)
recorder ((k -> NormalizedFilePath -> Action (Maybe v)) -> Rules ())
-> (k -> NormalizedFilePath -> Action (Maybe v)) -> Rules ()
forall a b. (a -> b) -> a -> b
$ \k
k NormalizedFilePath
file -> do
if NormalizedFilePath
file NormalizedFilePath -> NormalizedFilePath -> Bool
forall a. Eq a => a -> a -> Bool
== NormalizedFilePath
emptyFilePath then do v
res <- k -> Action v
f k
k; Maybe v -> Action (Maybe v)
forall (m :: * -> *) a. Monad m => a -> m a
return (v -> Maybe v
forall a. a -> Maybe a
Just v
res) else
String -> Action (Maybe v)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Action (Maybe v)) -> String -> Action (Maybe v)
forall a b. (a -> b) -> a -> b
$ String
"Rule " String -> ShowS
forall a. [a] -> [a] -> [a]
++ k -> String
forall a. Show a => a -> String
show k
k String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" should always be called with the empty string for a file"
defineEarlyCutOffNoFile :: IdeRule k v => Recorder (WithPriority Log) -> (k -> Action (BS.ByteString, v)) -> Rules ()
defineEarlyCutOffNoFile :: Recorder (WithPriority Log)
-> (k -> Action (ByteString, v)) -> Rules ()
defineEarlyCutOffNoFile Recorder (WithPriority Log)
recorder k -> Action (ByteString, v)
f = Recorder (WithPriority Log) -> RuleBody k v -> Rules ()
forall k v.
IdeRule k v =>
Recorder (WithPriority Log) -> RuleBody k v -> Rules ()
defineEarlyCutoff Recorder (WithPriority Log)
recorder (RuleBody k v -> Rules ()) -> RuleBody k v -> Rules ()
forall a b. (a -> b) -> a -> b
$ (k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v))
-> RuleBody k v
forall k v.
(k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v))
-> RuleBody k v
RuleNoDiagnostics ((k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v))
-> RuleBody k v)
-> (k -> NormalizedFilePath -> Action (Maybe ByteString, Maybe v))
-> RuleBody k v
forall a b. (a -> b) -> a -> b
$ \k
k NormalizedFilePath
file -> do
if NormalizedFilePath
file NormalizedFilePath -> NormalizedFilePath -> Bool
forall a. Eq a => a -> a -> Bool
== NormalizedFilePath
emptyFilePath then do (ByteString
hash, v
res) <- k -> Action (ByteString, v)
f k
k; (Maybe ByteString, Maybe v) -> Action (Maybe ByteString, Maybe v)
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
hash, v -> Maybe v
forall a. a -> Maybe a
Just v
res) else
String -> Action (Maybe ByteString, Maybe v)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Action (Maybe ByteString, Maybe v))
-> String -> Action (Maybe ByteString, Maybe v)
forall a b. (a -> b) -> a -> b
$ String
"Rule " String -> ShowS
forall a. [a] -> [a] -> [a]
++ k -> String
forall a. Show a => a -> String
show k
k String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" should always be called with the empty string for a file"
defineEarlyCutoff'
:: forall k v. IdeRule k v
=> (TextDocumentVersion -> [FileDiagnostic] -> Action ())
-> (BS.ByteString -> BS.ByteString -> Bool)
-> k
-> NormalizedFilePath
-> Maybe BS.ByteString
-> RunMode
-> (Value v -> Action (Maybe BS.ByteString, IdeResult v))
-> Action (RunResult (A (RuleResult k)))
defineEarlyCutoff' :: (TextDocumentVersion -> [FileDiagnostic] -> Action ())
-> (ByteString -> ByteString -> Bool)
-> k
-> NormalizedFilePath
-> Maybe ByteString
-> RunMode
-> (Value v -> Action (Maybe ByteString, IdeResult v))
-> Action (RunResult (A (RuleResult k)))
defineEarlyCutoff' TextDocumentVersion -> [FileDiagnostic] -> Action ()
doDiagnostics ByteString -> ByteString -> Bool
cmp k
key NormalizedFilePath
file Maybe ByteString
old RunMode
mode Value v -> Action (Maybe ByteString, IdeResult v)
action = do
ShakeExtras{Values
state :: Values
$sel:state:ShakeExtras :: ShakeExtras -> Values
state, ProgressReporting
progress :: ProgressReporting
$sel:progress:ShakeExtras :: ShakeExtras -> ProgressReporting
progress, TVar (HashSet Key)
dirtyKeys :: TVar (HashSet Key)
$sel:dirtyKeys:ShakeExtras :: ShakeExtras -> TVar (HashSet Key)
dirtyKeys} <- Action ShakeExtras
getShakeExtras
IdeOptions
options <- Action IdeOptions
getIdeOptions
(if IdeOptions -> k -> Bool
IdeOptions -> forall a. Typeable a => a -> Bool
optSkipProgress IdeOptions
options k
key then Action (RunResult (A v)) -> Action (RunResult (A v))
forall a. a -> a
id else ProgressReporting
-> NormalizedFilePath
-> Action (RunResult (A v))
-> Action (RunResult (A v))
ProgressReporting
-> forall a. NormalizedFilePath -> Action a -> Action a
inProgress ProgressReporting
progress NormalizedFilePath
file) (Action (RunResult (A v)) -> Action (RunResult (A v)))
-> Action (RunResult (A v)) -> Action (RunResult (A v))
forall a b. (a -> b) -> a -> b
$ do
Maybe (RunResult (A v))
val <- case Maybe ByteString
old of
Just ByteString
old | RunMode
mode RunMode -> RunMode -> Bool
forall a. Eq a => a -> a -> Bool
== RunMode
RunDependenciesSame -> do
Maybe (Value v, Vector FileDiagnostic)
v <- IO (Maybe (Value v, Vector FileDiagnostic))
-> Action (Maybe (Value v, Vector FileDiagnostic))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe (Value v, Vector FileDiagnostic))
-> Action (Maybe (Value v, Vector FileDiagnostic)))
-> IO (Maybe (Value v, Vector FileDiagnostic))
-> Action (Maybe (Value v, Vector FileDiagnostic))
forall a b. (a -> b) -> a -> b
$ String
-> STM (Maybe (Value v, Vector FileDiagnostic))
-> IO (Maybe (Value v, Vector FileDiagnostic))
forall a. String -> STM a -> IO a
atomicallyNamed String
"define - read 1" (STM (Maybe (Value v, Vector FileDiagnostic))
-> IO (Maybe (Value v, Vector FileDiagnostic)))
-> STM (Maybe (Value v, Vector FileDiagnostic))
-> IO (Maybe (Value v, Vector FileDiagnostic))
forall a b. (a -> b) -> a -> b
$ Values
-> k
-> NormalizedFilePath
-> STM (Maybe (Value v, Vector FileDiagnostic))
forall k v.
IdeRule k v =>
Values
-> k
-> NormalizedFilePath
-> STM (Maybe (Value v, Vector FileDiagnostic))
getValues Values
state k
key NormalizedFilePath
file
case Maybe (Value v, Vector FileDiagnostic)
v of
Just (v :: Value v
v@(Succeeded Maybe FileVersion
_ v
x), Vector FileDiagnostic
diags) -> do
Maybe FileVersion
ver <- k -> Maybe v -> NormalizedFilePath -> Action (Maybe FileVersion)
forall k v.
IdeRule k v =>
k -> Maybe v -> NormalizedFilePath -> Action (Maybe FileVersion)
estimateFileVersionUnsafely k
key (v -> Maybe v
forall a. a -> Maybe a
Just v
x) NormalizedFilePath
file
TextDocumentVersion -> [FileDiagnostic] -> Action ()
doDiagnostics (FileVersion -> TextDocumentVersion
vfsVersion (FileVersion -> TextDocumentVersion)
-> Maybe FileVersion -> TextDocumentVersion
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe FileVersion
ver) ([FileDiagnostic] -> Action ()) -> [FileDiagnostic] -> Action ()
forall a b. (a -> b) -> a -> b
$ Vector FileDiagnostic -> [FileDiagnostic]
forall a. Vector a -> [a]
Vector.toList Vector FileDiagnostic
diags
Maybe (RunResult (A v)) -> Action (Maybe (RunResult (A v)))
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe (RunResult (A v)) -> Action (Maybe (RunResult (A v))))
-> Maybe (RunResult (A v)) -> Action (Maybe (RunResult (A v)))
forall a b. (a -> b) -> a -> b
$ RunResult (A v) -> Maybe (RunResult (A v))
forall a. a -> Maybe a
Just (RunResult (A v) -> Maybe (RunResult (A v)))
-> RunResult (A v) -> Maybe (RunResult (A v))
forall a b. (a -> b) -> a -> b
$ RunChanged -> ByteString -> A v -> RunResult (A v)
forall value. RunChanged -> ByteString -> value -> RunResult value
RunResult RunChanged
ChangedNothing ByteString
old (A v -> RunResult (A v)) -> A v -> RunResult (A v)
forall a b. (a -> b) -> a -> b
$ Value v -> A v
forall v. Value v -> A v
A Value v
v
Maybe (Value v, Vector FileDiagnostic)
_ -> Maybe (RunResult (A v)) -> Action (Maybe (RunResult (A v)))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (RunResult (A v))
forall a. Maybe a
Nothing
Maybe ByteString
_ ->
Bool
-> Action (Maybe (RunResult (A v)))
-> Action (Maybe (RunResult (A v)))
forall a. HasCallStack => Bool -> a -> a
assert (RunMode
mode RunMode -> RunMode -> Bool
forall a. Eq a => a -> a -> Bool
/= RunMode
RunDependenciesSame) (Action (Maybe (RunResult (A v)))
-> Action (Maybe (RunResult (A v))))
-> Action (Maybe (RunResult (A v)))
-> Action (Maybe (RunResult (A v)))
forall a b. (a -> b) -> a -> b
$ Maybe (RunResult (A v)) -> Action (Maybe (RunResult (A v)))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (RunResult (A v))
forall a. Maybe a
Nothing
RunResult (A v)
res <- case Maybe (RunResult (A v))
val of
Just RunResult (A v)
res -> RunResult (A v) -> Action (RunResult (A v))
forall (m :: * -> *) a. Monad m => a -> m a
return RunResult (A v)
res
Maybe (RunResult (A v))
Nothing -> do
Value v
staleV <- IO (Value v) -> Action (Value v)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Value v) -> Action (Value v))
-> IO (Value v) -> Action (Value v)
forall a b. (a -> b) -> a -> b
$ String -> STM (Value v) -> IO (Value v)
forall a. String -> STM a -> IO a
atomicallyNamed String
"define -read 3" (STM (Value v) -> IO (Value v)) -> STM (Value v) -> IO (Value v)
forall a b. (a -> b) -> a -> b
$ Values
-> k
-> NormalizedFilePath
-> STM (Maybe (Value v, Vector FileDiagnostic))
forall k v.
IdeRule k v =>
Values
-> k
-> NormalizedFilePath
-> STM (Maybe (Value v, Vector FileDiagnostic))
getValues Values
state k
key NormalizedFilePath
file STM (Maybe (Value v, Vector FileDiagnostic))
-> (Maybe (Value v, Vector FileDiagnostic) -> Value v)
-> STM (Value v)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \case
Maybe (Value v, Vector FileDiagnostic)
Nothing -> Bool -> Value v
forall v. Bool -> Value v
Failed Bool
False
Just (Succeeded Maybe FileVersion
ver v
v, Vector FileDiagnostic
_) -> Maybe PositionDelta -> Maybe FileVersion -> v -> Value v
forall v. Maybe PositionDelta -> Maybe FileVersion -> v -> Value v
Stale Maybe PositionDelta
forall a. Maybe a
Nothing Maybe FileVersion
ver v
v
Just (Stale Maybe PositionDelta
d Maybe FileVersion
ver v
v, Vector FileDiagnostic
_) -> Maybe PositionDelta -> Maybe FileVersion -> v -> Value v
forall v. Maybe PositionDelta -> Maybe FileVersion -> v -> Value v
Stale Maybe PositionDelta
d Maybe FileVersion
ver v
v
Just (Failed Bool
b, Vector FileDiagnostic
_) -> Bool -> Value v
forall v. Bool -> Value v
Failed Bool
b
(Maybe ByteString
bs, ([FileDiagnostic]
diags, Maybe v
res)) <- Action (Maybe ByteString, IdeResult v)
-> (SomeException -> Action (Maybe ByteString, IdeResult v))
-> Action (Maybe ByteString, IdeResult v)
forall e a. Exception e => Action a -> (e -> Action a) -> Action a
actionCatch
(do (Maybe ByteString, IdeResult v)
v <- Value v -> Action (Maybe ByteString, IdeResult v)
action Value v
staleV; IO (Maybe ByteString, IdeResult v)
-> Action (Maybe ByteString, IdeResult v)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ByteString, IdeResult v)
-> Action (Maybe ByteString, IdeResult v))
-> IO (Maybe ByteString, IdeResult v)
-> Action (Maybe ByteString, IdeResult v)
forall a b. (a -> b) -> a -> b
$ (Maybe ByteString, IdeResult v)
-> IO (Maybe ByteString, IdeResult v)
forall a. a -> IO a
evaluate ((Maybe ByteString, IdeResult v)
-> IO (Maybe ByteString, IdeResult v))
-> (Maybe ByteString, IdeResult v)
-> IO (Maybe ByteString, IdeResult v)
forall a b. (a -> b) -> a -> b
$ (Maybe ByteString, IdeResult v) -> (Maybe ByteString, IdeResult v)
forall a. NFData a => a -> a
force (Maybe ByteString, IdeResult v)
v) ((SomeException -> Action (Maybe ByteString, IdeResult v))
-> Action (Maybe ByteString, IdeResult v))
-> (SomeException -> Action (Maybe ByteString, IdeResult v))
-> Action (Maybe ByteString, IdeResult v)
forall a b. (a -> b) -> a -> b
$
\(SomeException
e :: SomeException) -> do
(Maybe ByteString, IdeResult v)
-> Action (Maybe ByteString, IdeResult v)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe ByteString
forall a. Maybe a
Nothing, ([NormalizedFilePath -> Text -> FileDiagnostic
ideErrorText NormalizedFilePath
file (Text -> FileDiagnostic) -> Text -> FileDiagnostic
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ SomeException -> String
forall a. Show a => a -> String
show SomeException
e | Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ SomeException -> Bool
isBadDependency SomeException
e],Maybe v
forall a. Maybe a
Nothing))
Maybe FileVersion
ver <- k -> Maybe v -> NormalizedFilePath -> Action (Maybe FileVersion)
forall k v.
IdeRule k v =>
k -> Maybe v -> NormalizedFilePath -> Action (Maybe FileVersion)
estimateFileVersionUnsafely k
key Maybe v
res NormalizedFilePath
file
(ShakeValue
bs, Value v
res) <- case Maybe v
res of
Maybe v
Nothing -> do
(ShakeValue, Value v) -> Action (ShakeValue, Value v)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((ByteString -> ShakeValue) -> Maybe ByteString -> ShakeValue
toShakeValue ByteString -> ShakeValue
ShakeStale Maybe ByteString
bs, Value v
staleV)
Just v
v -> (ShakeValue, Value v) -> Action (ShakeValue, Value v)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ShakeValue
-> (ByteString -> ShakeValue) -> Maybe ByteString -> ShakeValue
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ShakeValue
ShakeNoCutoff ByteString -> ShakeValue
ShakeResult Maybe ByteString
bs, Maybe FileVersion -> v -> Value v
forall v. Maybe FileVersion -> v -> Value v
Succeeded Maybe FileVersion
ver v
v)
IO () -> Action ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Action ()) -> IO () -> Action ()
forall a b. (a -> b) -> a -> b
$ String -> STM () -> IO ()
forall a. String -> STM a -> IO a
atomicallyNamed String
"define - write" (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ Values
-> k
-> NormalizedFilePath
-> Value v
-> Vector FileDiagnostic
-> STM ()
forall k v.
IdeRule k v =>
Values
-> k
-> NormalizedFilePath
-> Value v
-> Vector FileDiagnostic
-> STM ()
setValues Values
state k
key NormalizedFilePath
file Value v
res ([FileDiagnostic] -> Vector FileDiagnostic
forall a. [a] -> Vector a
Vector.fromList [FileDiagnostic]
diags)
TextDocumentVersion -> [FileDiagnostic] -> Action ()
doDiagnostics (FileVersion -> TextDocumentVersion
vfsVersion (FileVersion -> TextDocumentVersion)
-> Maybe FileVersion -> TextDocumentVersion
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe FileVersion
ver) [FileDiagnostic]
diags
let eq :: Bool
eq = case (ShakeValue
bs, (ByteString -> ShakeValue) -> Maybe ByteString -> Maybe ShakeValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> ShakeValue
decodeShakeValue Maybe ByteString
old) of
(ShakeResult ByteString
a, Just (ShakeResult ByteString
b)) -> ByteString -> ByteString -> Bool
cmp ByteString
a ByteString
b
(ShakeStale ByteString
a, Just (ShakeStale ByteString
b)) -> ByteString -> ByteString -> Bool
cmp ByteString
a ByteString
b
(ShakeValue, Maybe ShakeValue)
_ -> Bool
False
RunResult (A v) -> Action (RunResult (A v))
forall (m :: * -> *) a. Monad m => a -> m a
return (RunResult (A v) -> Action (RunResult (A v)))
-> RunResult (A v) -> Action (RunResult (A v))
forall a b. (a -> b) -> a -> b
$ RunChanged -> ByteString -> A v -> RunResult (A v)
forall value. RunChanged -> ByteString -> value -> RunResult value
RunResult
(if Bool
eq then RunChanged
ChangedRecomputeSame else RunChanged
ChangedRecomputeDiff)
(ShakeValue -> ByteString
encodeShakeValue ShakeValue
bs) (A v -> RunResult (A v)) -> A v -> RunResult (A v)
forall a b. (a -> b) -> a -> b
$
Value v -> A v
forall v. Value v -> A v
A Value v
res
IO () -> Action ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Action ()) -> IO () -> Action ()
forall a b. (a -> b) -> a -> b
$ String -> STM () -> IO ()
forall a. String -> STM a -> IO a
atomicallyNamed String
"define - dirtyKeys" (STM () -> IO ()) -> STM () -> IO ()
forall a b. (a -> b) -> a -> b
$ TVar (HashSet Key) -> (HashSet Key -> HashSet Key) -> STM ()
forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' TVar (HashSet Key)
dirtyKeys (Key -> HashSet Key -> HashSet Key
forall a. (Eq a, Hashable a) => a -> HashSet a -> HashSet a
HSet.delete (Key -> HashSet Key -> HashSet Key)
-> Key -> HashSet Key -> HashSet Key
forall a b. (a -> b) -> a -> b
$ k -> NormalizedFilePath -> Key
forall k. ShakeValue k => k -> NormalizedFilePath -> Key
toKey k
key NormalizedFilePath
file)
RunResult (A v) -> Action (RunResult (A v))
forall (m :: * -> *) a. Monad m => a -> m a
return RunResult (A v)
res
where
estimateFileVersionUnsafely
:: forall k v
. IdeRule k v
=> k
-> Maybe v
-> NormalizedFilePath
-> Action (Maybe FileVersion)
estimateFileVersionUnsafely :: k -> Maybe v -> NormalizedFilePath -> Action (Maybe FileVersion)
estimateFileVersionUnsafely k
_k Maybe v
v NormalizedFilePath
fp
| NormalizedFilePath
fp NormalizedFilePath -> NormalizedFilePath -> Bool
forall a. Eq a => a -> a -> Bool
== NormalizedFilePath
emptyFilePath = Maybe FileVersion -> Action (Maybe FileVersion)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe FileVersion
forall a. Maybe a
Nothing
| Just k :~: GetModificationTime
Refl <- (Typeable k, Typeable GetModificationTime) =>
Maybe (k :~: GetModificationTime)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @k @GetModificationTime = Maybe v -> Action (Maybe v)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe v
v
| Just k :~: AddWatchedFile
Refl <- (Typeable k, Typeable AddWatchedFile) =>
Maybe (k :~: AddWatchedFile)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @k @AddWatchedFile = Maybe FileVersion -> Action (Maybe FileVersion)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe FileVersion
forall a. Maybe a
Nothing
| Just k :~: IsFileOfInterest
Refl <- (Typeable k, Typeable IsFileOfInterest) =>
Maybe (k :~: IsFileOfInterest)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @k @IsFileOfInterest = Maybe FileVersion -> Action (Maybe FileVersion)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe FileVersion
forall a. Maybe a
Nothing
| Just k :~: GetFileExists
Refl <- (Typeable k, Typeable GetFileExists) => Maybe (k :~: GetFileExists)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @k @GetFileExists = Maybe FileVersion -> Action (Maybe FileVersion)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe FileVersion
forall a. Maybe a
Nothing
| Bool
otherwise = GetModificationTime
-> NormalizedFilePath -> Action (Maybe FileVersion)
forall k v.
IdeRule k v =>
k -> NormalizedFilePath -> Action (Maybe v)
useWithoutDependency (Bool -> GetModificationTime
GetModificationTime_ Bool
False) NormalizedFilePath
fp
traceA :: A v -> String
traceA :: A v -> String
traceA (A Failed{}) = String
"Failed"
traceA (A Stale{}) = String
"Stale"
traceA (A Succeeded{}) = String
"Success"
updateFileDiagnostics :: MonadIO m
=> Recorder (WithPriority Log)
-> NormalizedFilePath
-> TextDocumentVersion
-> Key
-> ShakeExtras
-> [(ShowDiagnostic,Diagnostic)]
-> m ()
updateFileDiagnostics :: Recorder (WithPriority Log)
-> NormalizedFilePath
-> TextDocumentVersion
-> Key
-> ShakeExtras
-> [(ShowDiagnostic, Diagnostic)]
-> m ()
updateFileDiagnostics Recorder (WithPriority Log)
recorder NormalizedFilePath
fp TextDocumentVersion
ver Key
k ShakeExtras{STMDiagnosticStore
diagnostics :: STMDiagnosticStore
$sel:diagnostics:ShakeExtras :: ShakeExtras -> STMDiagnosticStore
diagnostics, STMDiagnosticStore
hiddenDiagnostics :: STMDiagnosticStore
$sel:hiddenDiagnostics:ShakeExtras :: ShakeExtras -> STMDiagnosticStore
hiddenDiagnostics, Map NormalizedUri [Diagnostic]
publishedDiagnostics :: Map NormalizedUri [Diagnostic]
$sel:publishedDiagnostics:ShakeExtras :: ShakeExtras -> Map NormalizedUri [Diagnostic]
publishedDiagnostics, Debouncer NormalizedUri
debouncer :: Debouncer NormalizedUri
$sel:debouncer:ShakeExtras :: ShakeExtras -> Debouncer NormalizedUri
debouncer, Maybe (LanguageContextEnv Config)
lspEnv :: Maybe (LanguageContextEnv Config)
$sel:lspEnv:ShakeExtras :: ShakeExtras -> Maybe (LanguageContextEnv Config)
lspEnv} [(ShowDiagnostic, Diagnostic)]
current =
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ String -> ((String -> String -> IO ()) -> IO ()) -> IO ()
forall (m :: * -> *) a.
(MonadMask m, MonadIO m) =>
String -> ((String -> String -> m ()) -> m a) -> m a
withTrace (String
"update diagnostics " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
forall a. IsString a => String -> a
fromString(NormalizedFilePath -> String
fromNormalizedFilePath NormalizedFilePath
fp)) (((String -> String -> IO ()) -> IO ()) -> IO ())
-> ((String -> String -> IO ()) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ String -> String -> IO ()
addTag -> do
String -> String -> IO ()
addTag String
"key" (Key -> String
forall a. Show a => a -> String
show Key
k)
let ([(ShowDiagnostic, Diagnostic)]
currentShown, [(ShowDiagnostic, Diagnostic)]
currentHidden) = ((ShowDiagnostic, Diagnostic) -> Bool)
-> [(ShowDiagnostic, Diagnostic)]
-> ([(ShowDiagnostic, Diagnostic)], [(ShowDiagnostic, Diagnostic)])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition ((ShowDiagnostic -> ShowDiagnostic -> Bool
forall a. Eq a => a -> a -> Bool
== ShowDiagnostic
ShowDiag) (ShowDiagnostic -> Bool)
-> ((ShowDiagnostic, Diagnostic) -> ShowDiagnostic)
-> (ShowDiagnostic, Diagnostic)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ShowDiagnostic, Diagnostic) -> ShowDiagnostic
forall a b. (a, b) -> a
fst) [(ShowDiagnostic, Diagnostic)]
current
uri :: NormalizedUri
uri = NormalizedFilePath -> NormalizedUri
filePathToUri' NormalizedFilePath
fp
addTagUnsafe :: String -> String -> String -> a -> a
addTagUnsafe :: String -> String -> String -> a -> a
addTagUnsafe String
msg String
t String
x a
v = IO () -> ()
forall a. IO a -> a
unsafePerformIO(String -> String -> IO ()
addTag (String
msg String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
t) String
x) () -> a -> a
`seq` a
v
update :: (forall a. String -> String -> a -> a) -> [Diagnostic] -> STMDiagnosticStore -> STM [Diagnostic]
update :: (forall a. String -> String -> a -> a)
-> [Diagnostic] -> STMDiagnosticStore -> STM [Diagnostic]
update forall a. String -> String -> a -> a
addTagUnsafe [Diagnostic]
new STMDiagnosticStore
store = String -> String -> STM [Diagnostic] -> STM [Diagnostic]
forall a. String -> String -> a -> a
addTagUnsafe String
"count" (Int -> String
forall a. Show a => a -> String
show (Int -> String) -> Int -> String
forall a b. (a -> b) -> a -> b
$ [Diagnostic] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
Prelude.length [Diagnostic]
new) (STM [Diagnostic] -> STM [Diagnostic])
-> STM [Diagnostic] -> STM [Diagnostic]
forall a b. (a -> b) -> a -> b
$ (forall a. String -> String -> a -> a)
-> NormalizedUri
-> TextDocumentVersion
-> Text
-> [Diagnostic]
-> STMDiagnosticStore
-> STM [Diagnostic]
setStageDiagnostics forall a. String -> String -> a -> a
addTagUnsafe NormalizedUri
uri TextDocumentVersion
ver (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Key -> String
forall a. Show a => a -> String
show Key
k) [Diagnostic]
new STMDiagnosticStore
store
String -> String -> IO ()
addTag String
"version" (TextDocumentVersion -> String
forall a. Show a => a -> String
show TextDocumentVersion
ver)
IO () -> IO ()
forall a. IO a -> IO a
mask_ (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
[Diagnostic]
newDiags <- IO [Diagnostic] -> IO [Diagnostic]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Diagnostic] -> IO [Diagnostic])
-> IO [Diagnostic] -> IO [Diagnostic]
forall a b. (a -> b) -> a -> b
$ String -> STM [Diagnostic] -> IO [Diagnostic]
forall a. String -> STM a -> IO a
atomicallyNamed String
"diagnostics - update" (STM [Diagnostic] -> IO [Diagnostic])
-> STM [Diagnostic] -> IO [Diagnostic]
forall a b. (a -> b) -> a -> b
$ (forall a. String -> String -> a -> a)
-> [Diagnostic] -> STMDiagnosticStore -> STM [Diagnostic]
update (String -> String -> String -> a -> a
forall a. String -> String -> String -> a -> a
addTagUnsafe String
"shown ") (((ShowDiagnostic, Diagnostic) -> Diagnostic)
-> [(ShowDiagnostic, Diagnostic)] -> [Diagnostic]
forall a b. (a -> b) -> [a] -> [b]
map (ShowDiagnostic, Diagnostic) -> Diagnostic
forall a b. (a, b) -> b
snd [(ShowDiagnostic, Diagnostic)]
currentShown) STMDiagnosticStore
diagnostics
[Diagnostic]
_ <- IO [Diagnostic] -> IO [Diagnostic]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Diagnostic] -> IO [Diagnostic])
-> IO [Diagnostic] -> IO [Diagnostic]
forall a b. (a -> b) -> a -> b
$ String -> STM [Diagnostic] -> IO [Diagnostic]
forall a. String -> STM a -> IO a
atomicallyNamed String
"diagnostics - hidden" (STM [Diagnostic] -> IO [Diagnostic])
-> STM [Diagnostic] -> IO [Diagnostic]
forall a b. (a -> b) -> a -> b
$ (forall a. String -> String -> a -> a)
-> [Diagnostic] -> STMDiagnosticStore -> STM [Diagnostic]
update (String -> String -> String -> a -> a
forall a. String -> String -> String -> a -> a
addTagUnsafe String
"hidden ") (((ShowDiagnostic, Diagnostic) -> Diagnostic)
-> [(ShowDiagnostic, Diagnostic)] -> [Diagnostic]
forall a b. (a -> b) -> [a] -> [b]
map (ShowDiagnostic, Diagnostic) -> Diagnostic
forall a b. (a, b) -> b
snd [(ShowDiagnostic, Diagnostic)]
currentHidden) STMDiagnosticStore
hiddenDiagnostics
let uri :: NormalizedUri
uri = NormalizedFilePath -> NormalizedUri
filePathToUri' NormalizedFilePath
fp
let delay :: Seconds
delay = if [Diagnostic] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Diagnostic]
newDiags then Seconds
0.1 else Seconds
0
Debouncer NormalizedUri
-> Seconds -> NormalizedUri -> IO () -> IO ()
forall k. Debouncer k -> Seconds -> k -> IO () -> IO ()
registerEvent Debouncer NormalizedUri
debouncer Seconds
delay NormalizedUri
uri (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> ((String -> String -> IO ()) -> IO ()) -> IO ()
forall (m :: * -> *) a.
(MonadMask m, MonadIO m) =>
String -> ((String -> String -> m ()) -> m a) -> m a
withTrace (String
"report diagnostics " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> ShowS
forall a. IsString a => String -> a
fromString (NormalizedFilePath -> String
fromNormalizedFilePath NormalizedFilePath
fp)) (((String -> String -> IO ()) -> IO ()) -> IO ())
-> ((String -> String -> IO ()) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \String -> String -> IO ()
tag -> do
IO (IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (IO (IO ()) -> IO ()) -> IO (IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ IO (IO ()) -> IO (IO ())
forall a. IO a -> IO a
mask_ (IO (IO ()) -> IO (IO ())) -> IO (IO ()) -> IO (IO ())
forall a b. (a -> b) -> a -> b
$ do
[Diagnostic]
lastPublish <- String -> STM [Diagnostic] -> IO [Diagnostic]
forall a. String -> STM a -> IO a
atomicallyNamed String
"diagnostics - publish" (STM [Diagnostic] -> IO [Diagnostic])
-> STM [Diagnostic] -> IO [Diagnostic]
forall a b. (a -> b) -> a -> b
$ Focus [Diagnostic] STM [Diagnostic]
-> NormalizedUri
-> Map NormalizedUri [Diagnostic]
-> STM [Diagnostic]
forall key value result.
(Eq key, Hashable key) =>
Focus value STM result -> key -> Map key value -> STM result
STM.focus ([Diagnostic] -> Focus [Diagnostic] STM [Diagnostic]
forall (m :: * -> *) a. Monad m => a -> Focus a m a
Focus.lookupWithDefault [] Focus [Diagnostic] STM [Diagnostic]
-> Focus [Diagnostic] STM () -> Focus [Diagnostic] STM [Diagnostic]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* [Diagnostic] -> Focus [Diagnostic] STM ()
forall (m :: * -> *) a. Monad m => a -> Focus a m ()
Focus.insert [Diagnostic]
newDiags) NormalizedUri
uri Map NormalizedUri [Diagnostic]
publishedDiagnostics
let action :: IO ()
action = Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([Diagnostic]
lastPublish [Diagnostic] -> [Diagnostic] -> Bool
forall a. Eq a => a -> a -> Bool
/= [Diagnostic]
newDiags) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ case Maybe (LanguageContextEnv Config)
lspEnv of
Maybe (LanguageContextEnv Config)
Nothing ->
Recorder (WithPriority Log) -> Priority -> Log -> IO ()
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Info (Log -> IO ()) -> Log -> IO ()
forall a b. (a -> b) -> a -> b
$ [FileDiagnostic] -> Log
LogDiagsDiffButNoLspEnv ((Diagnostic -> FileDiagnostic) -> [Diagnostic] -> [FileDiagnostic]
forall a b. (a -> b) -> [a] -> [b]
map (NormalizedFilePath
fp, ShowDiagnostic
ShowDiag,) [Diagnostic]
newDiags)
Just LanguageContextEnv Config
env -> LanguageContextEnv Config -> LspT Config IO () -> IO ()
forall config (m :: * -> *) a.
LanguageContextEnv config -> LspT config m a -> m a
LSP.runLspT LanguageContextEnv Config
env (LspT Config IO () -> IO ()) -> LspT Config IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
IO () -> LspT Config IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> LspT Config IO ()) -> IO () -> LspT Config IO ()
forall a b. (a -> b) -> a -> b
$ String -> String -> IO ()
tag String
"count" (Int -> String
forall a. Show a => a -> String
show (Int -> String) -> Int -> String
forall a b. (a -> b) -> a -> b
$ [Diagnostic] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
Prelude.length [Diagnostic]
newDiags)
IO () -> LspT Config IO ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> LspT Config IO ()) -> IO () -> LspT Config IO ()
forall a b. (a -> b) -> a -> b
$ String -> String -> IO ()
tag String
"key" (Key -> String
forall a. Show a => a -> String
show Key
k)
SServerMethod 'TextDocumentPublishDiagnostics
-> MessageParams 'TextDocumentPublishDiagnostics
-> LspT Config IO ()
forall (m :: Method 'FromServer 'Notification) (f :: * -> *)
config.
MonadLsp config f =>
SServerMethod m -> MessageParams m -> f ()
LSP.sendNotification SServerMethod 'TextDocumentPublishDiagnostics
LSP.STextDocumentPublishDiagnostics (MessageParams 'TextDocumentPublishDiagnostics
-> LspT Config IO ())
-> MessageParams 'TextDocumentPublishDiagnostics
-> LspT Config IO ()
forall a b. (a -> b) -> a -> b
$
Uri -> Maybe UInt -> List Diagnostic -> PublishDiagnosticsParams
LSP.PublishDiagnosticsParams (NormalizedUri -> Uri
fromNormalizedUri NormalizedUri
uri) ((Int32 -> UInt) -> TextDocumentVersion -> Maybe UInt
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int32 -> UInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral TextDocumentVersion
ver) ([Diagnostic] -> List Diagnostic
forall a. [a] -> List a
List [Diagnostic]
newDiags)
IO () -> IO (IO ())
forall (m :: * -> *) a. Monad m => a -> m a
return IO ()
action
newtype Priority = Priority Double
setPriority :: Priority -> Action ()
setPriority :: Priority -> Action ()
setPriority (Priority Seconds
p) = Seconds -> Action ()
reschedule Seconds
p
ideLogger :: IdeState -> Logger
ideLogger :: IdeState -> Logger
ideLogger IdeState{$sel:shakeExtras:IdeState :: IdeState -> ShakeExtras
shakeExtras=ShakeExtras{Logger
logger :: Logger
$sel:logger:ShakeExtras :: ShakeExtras -> Logger
logger}} = Logger
logger
actionLogger :: Action Logger
actionLogger :: Action Logger
actionLogger = do
ShakeExtras{Logger
logger :: Logger
$sel:logger:ShakeExtras :: ShakeExtras -> Logger
logger} <- Action ShakeExtras
getShakeExtras
Logger -> Action Logger
forall (m :: * -> *) a. Monad m => a -> m a
return Logger
logger
type STMDiagnosticStore = STM.Map NormalizedUri StoreItem
getDiagnosticsFromStore :: StoreItem -> [Diagnostic]
getDiagnosticsFromStore :: StoreItem -> [Diagnostic]
getDiagnosticsFromStore (StoreItem TextDocumentVersion
_ DiagnosticsBySource
diags) = (SortedList Diagnostic -> [Diagnostic])
-> [SortedList Diagnostic] -> [Diagnostic]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap SortedList Diagnostic -> [Diagnostic]
forall a. SortedList a -> [a]
SL.fromSortedList ([SortedList Diagnostic] -> [Diagnostic])
-> [SortedList Diagnostic] -> [Diagnostic]
forall a b. (a -> b) -> a -> b
$ DiagnosticsBySource -> [SortedList Diagnostic]
forall k a. Map k a -> [a]
Map.elems DiagnosticsBySource
diags
updateSTMDiagnostics ::
(forall a. String -> String -> a -> a) ->
STMDiagnosticStore ->
NormalizedUri ->
TextDocumentVersion ->
DiagnosticsBySource ->
STM [LSP.Diagnostic]
updateSTMDiagnostics :: (forall a. String -> String -> a -> a)
-> STMDiagnosticStore
-> NormalizedUri
-> TextDocumentVersion
-> DiagnosticsBySource
-> STM [Diagnostic]
updateSTMDiagnostics forall a. String -> String -> a -> a
addTag STMDiagnosticStore
store NormalizedUri
uri TextDocumentVersion
mv DiagnosticsBySource
newDiagsBySource =
StoreItem -> [Diagnostic]
getDiagnosticsFromStore (StoreItem -> [Diagnostic])
-> (Maybe StoreItem -> StoreItem)
-> Maybe StoreItem
-> [Diagnostic]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe StoreItem -> StoreItem
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe StoreItem -> [Diagnostic])
-> STM (Maybe StoreItem) -> STM [Diagnostic]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Focus StoreItem STM (Maybe StoreItem)
-> NormalizedUri -> STMDiagnosticStore -> STM (Maybe StoreItem)
forall key value result.
(Eq key, Hashable key) =>
Focus value STM result -> key -> Map key value -> STM result
STM.focus ((Maybe StoreItem -> Maybe StoreItem) -> Focus StoreItem STM ()
forall (m :: * -> *) a.
Monad m =>
(Maybe a -> Maybe a) -> Focus a m ()
Focus.alter Maybe StoreItem -> Maybe StoreItem
update Focus StoreItem STM ()
-> Focus StoreItem STM (Maybe StoreItem)
-> Focus StoreItem STM (Maybe StoreItem)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Focus StoreItem STM (Maybe StoreItem)
forall (m :: * -> *) a. Monad m => Focus a m (Maybe a)
Focus.lookup) NormalizedUri
uri STMDiagnosticStore
store
where
update :: Maybe StoreItem -> Maybe StoreItem
update (Just(StoreItem TextDocumentVersion
mvs DiagnosticsBySource
dbs))
| String -> String -> Bool -> Bool
forall a. String -> String -> a -> a
addTag String
"previous version" (TextDocumentVersion -> String
forall a. Show a => a -> String
show TextDocumentVersion
mvs) (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$
String -> String -> Bool -> Bool
forall a. String -> String -> a -> a
addTag String
"previous count" (Int -> String
forall a. Show a => a -> String
show (Int -> String) -> Int -> String
forall a b. (a -> b) -> a -> b
$ [SortedList Diagnostic] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
Prelude.length ([SortedList Diagnostic] -> Int) -> [SortedList Diagnostic] -> Int
forall a b. (a -> b) -> a -> b
$ (SortedList Diagnostic -> Bool)
-> [SortedList Diagnostic] -> [SortedList Diagnostic]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not(Bool -> Bool)
-> (SortedList Diagnostic -> Bool) -> SortedList Diagnostic -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.SortedList Diagnostic -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null) ([SortedList Diagnostic] -> [SortedList Diagnostic])
-> [SortedList Diagnostic] -> [SortedList Diagnostic]
forall a b. (a -> b) -> a -> b
$ DiagnosticsBySource -> [SortedList Diagnostic]
forall k a. Map k a -> [a]
Map.elems DiagnosticsBySource
dbs) Bool
False = Maybe StoreItem
forall a. HasCallStack => a
undefined
| TextDocumentVersion
mvs TextDocumentVersion -> TextDocumentVersion -> Bool
forall a. Eq a => a -> a -> Bool
== TextDocumentVersion
mv = StoreItem -> Maybe StoreItem
forall a. a -> Maybe a
Just (TextDocumentVersion -> DiagnosticsBySource -> StoreItem
StoreItem TextDocumentVersion
mv (DiagnosticsBySource
newDiagsBySource DiagnosticsBySource -> DiagnosticsBySource -> DiagnosticsBySource
forall a. Semigroup a => a -> a -> a
<> DiagnosticsBySource
dbs))
update Maybe StoreItem
_ = StoreItem -> Maybe StoreItem
forall a. a -> Maybe a
Just (TextDocumentVersion -> DiagnosticsBySource -> StoreItem
StoreItem TextDocumentVersion
mv DiagnosticsBySource
newDiagsBySource)
setStageDiagnostics
:: (forall a. String -> String -> a -> a)
-> NormalizedUri
-> TextDocumentVersion
-> T.Text
-> [LSP.Diagnostic]
-> STMDiagnosticStore
-> STM [LSP.Diagnostic]
setStageDiagnostics :: (forall a. String -> String -> a -> a)
-> NormalizedUri
-> TextDocumentVersion
-> Text
-> [Diagnostic]
-> STMDiagnosticStore
-> STM [Diagnostic]
setStageDiagnostics forall a. String -> String -> a -> a
addTag NormalizedUri
uri TextDocumentVersion
ver Text
stage [Diagnostic]
diags STMDiagnosticStore
ds = (forall a. String -> String -> a -> a)
-> STMDiagnosticStore
-> NormalizedUri
-> TextDocumentVersion
-> DiagnosticsBySource
-> STM [Diagnostic]
updateSTMDiagnostics forall a. String -> String -> a -> a
addTag STMDiagnosticStore
ds NormalizedUri
uri TextDocumentVersion
ver DiagnosticsBySource
updatedDiags
where
!updatedDiags :: DiagnosticsBySource
updatedDiags = Maybe Text -> SortedList Diagnostic -> DiagnosticsBySource
forall k a. k -> a -> Map k a
Map.singleton (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
stage) (SortedList Diagnostic -> DiagnosticsBySource)
-> SortedList Diagnostic -> DiagnosticsBySource
forall a b. (a -> b) -> a -> b
$! [Diagnostic] -> SortedList Diagnostic
forall a. Ord a => [a] -> SortedList a
SL.toSortedList [Diagnostic]
diags
getAllDiagnostics ::
STMDiagnosticStore ->
STM [FileDiagnostic]
getAllDiagnostics :: STMDiagnosticStore -> STM [FileDiagnostic]
getAllDiagnostics =
([(NormalizedUri, StoreItem)] -> [FileDiagnostic])
-> STM [(NormalizedUri, StoreItem)] -> STM [FileDiagnostic]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((NormalizedUri, StoreItem) -> [FileDiagnostic])
-> [(NormalizedUri, StoreItem)] -> [FileDiagnostic]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\(NormalizedUri
k,StoreItem
v) -> (Diagnostic -> FileDiagnostic) -> [Diagnostic] -> [FileDiagnostic]
forall a b. (a -> b) -> [a] -> [b]
map (NormalizedUri -> NormalizedFilePath
fromUri NormalizedUri
k,ShowDiagnostic
ShowDiag,) ([Diagnostic] -> [FileDiagnostic])
-> [Diagnostic] -> [FileDiagnostic]
forall a b. (a -> b) -> a -> b
$ StoreItem -> [Diagnostic]
getDiagnosticsFromStore StoreItem
v)) (STM [(NormalizedUri, StoreItem)] -> STM [FileDiagnostic])
-> (STMDiagnosticStore -> STM [(NormalizedUri, StoreItem)])
-> STMDiagnosticStore
-> STM [FileDiagnostic]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ListT STM (NormalizedUri, StoreItem)
-> STM [(NormalizedUri, StoreItem)]
forall (m :: * -> *) a. Monad m => ListT m a -> m [a]
ListT.toList (ListT STM (NormalizedUri, StoreItem)
-> STM [(NormalizedUri, StoreItem)])
-> (STMDiagnosticStore -> ListT STM (NormalizedUri, StoreItem))
-> STMDiagnosticStore
-> STM [(NormalizedUri, StoreItem)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. STMDiagnosticStore -> ListT STM (NormalizedUri, StoreItem)
forall key value. Map key value -> ListT STM (key, value)
STM.listT
updatePositionMapping :: IdeState -> VersionedTextDocumentIdentifier -> List TextDocumentContentChangeEvent -> STM ()
updatePositionMapping :: IdeState
-> VersionedTextDocumentIdentifier
-> List TextDocumentContentChangeEvent
-> STM ()
updatePositionMapping IdeState{$sel:shakeExtras:IdeState :: IdeState -> ShakeExtras
shakeExtras = ShakeExtras{Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
positionMapping :: Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
$sel:positionMapping:ShakeExtras :: ShakeExtras
-> Map
NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
positionMapping}} VersionedTextDocumentIdentifier{TextDocumentVersion
Uri
$sel:_uri:VersionedTextDocumentIdentifier :: VersionedTextDocumentIdentifier -> Uri
$sel:_version:VersionedTextDocumentIdentifier :: VersionedTextDocumentIdentifier -> TextDocumentVersion
_version :: TextDocumentVersion
_uri :: Uri
..} (List [TextDocumentContentChangeEvent]
changes) =
Focus (EnumMap Int32 (PositionDelta, PositionMapping)) STM ()
-> NormalizedUri
-> Map
NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
-> STM ()
forall key value result.
(Eq key, Hashable key) =>
Focus value STM result -> key -> Map key value -> STM result
STM.focus ((Maybe (EnumMap Int32 (PositionDelta, PositionMapping))
-> Maybe (EnumMap Int32 (PositionDelta, PositionMapping)))
-> Focus (EnumMap Int32 (PositionDelta, PositionMapping)) STM ()
forall (m :: * -> *) a.
Monad m =>
(Maybe a -> Maybe a) -> Focus a m ()
Focus.alter Maybe (EnumMap Int32 (PositionDelta, PositionMapping))
-> Maybe (EnumMap Int32 (PositionDelta, PositionMapping))
f) NormalizedUri
uri Map NormalizedUri (EnumMap Int32 (PositionDelta, PositionMapping))
positionMapping
where
uri :: NormalizedUri
uri = Uri -> NormalizedUri
toNormalizedUri Uri
_uri
f :: Maybe (EnumMap Int32 (PositionDelta, PositionMapping))
-> Maybe (EnumMap Int32 (PositionDelta, PositionMapping))
f = EnumMap Int32 (PositionDelta, PositionMapping)
-> Maybe (EnumMap Int32 (PositionDelta, PositionMapping))
forall a. a -> Maybe a
Just (EnumMap Int32 (PositionDelta, PositionMapping)
-> Maybe (EnumMap Int32 (PositionDelta, PositionMapping)))
-> (Maybe (EnumMap Int32 (PositionDelta, PositionMapping))
-> EnumMap Int32 (PositionDelta, PositionMapping))
-> Maybe (EnumMap Int32 (PositionDelta, PositionMapping))
-> Maybe (EnumMap Int32 (PositionDelta, PositionMapping))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EnumMap Int32 (PositionDelta, PositionMapping)
-> EnumMap Int32 (PositionDelta, PositionMapping)
f' (EnumMap Int32 (PositionDelta, PositionMapping)
-> EnumMap Int32 (PositionDelta, PositionMapping))
-> (Maybe (EnumMap Int32 (PositionDelta, PositionMapping))
-> EnumMap Int32 (PositionDelta, PositionMapping))
-> Maybe (EnumMap Int32 (PositionDelta, PositionMapping))
-> EnumMap Int32 (PositionDelta, PositionMapping)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EnumMap Int32 (PositionDelta, PositionMapping)
-> Maybe (EnumMap Int32 (PositionDelta, PositionMapping))
-> EnumMap Int32 (PositionDelta, PositionMapping)
forall a. a -> Maybe a -> a
fromMaybe EnumMap Int32 (PositionDelta, PositionMapping)
forall a. Monoid a => a
mempty
f' :: EnumMap Int32 (PositionDelta, PositionMapping)
-> EnumMap Int32 (PositionDelta, PositionMapping)
f' EnumMap Int32 (PositionDelta, PositionMapping)
mappingForUri = (PositionMapping, EnumMap Int32 (PositionDelta, PositionMapping))
-> EnumMap Int32 (PositionDelta, PositionMapping)
forall a b. (a, b) -> b
snd ((PositionMapping, EnumMap Int32 (PositionDelta, PositionMapping))
-> EnumMap Int32 (PositionDelta, PositionMapping))
-> (PositionMapping,
EnumMap Int32 (PositionDelta, PositionMapping))
-> EnumMap Int32 (PositionDelta, PositionMapping)
forall a b. (a -> b) -> a -> b
$
(PositionMapping
-> Int32
-> (PositionDelta, PositionMapping)
-> (PositionMapping, (PositionDelta, PositionMapping)))
-> PositionMapping
-> EnumMap Int32 (PositionDelta, PositionMapping)
-> (PositionMapping,
EnumMap Int32 (PositionDelta, PositionMapping))
forall k a b c.
Enum k =>
(a -> k -> b -> (a, c)) -> a -> EnumMap k b -> (a, EnumMap k c)
EM.mapAccumRWithKey (\PositionMapping
acc Int32
_k (PositionDelta
delta, PositionMapping
_) -> let new :: PositionMapping
new = PositionDelta -> PositionMapping -> PositionMapping
addDelta PositionDelta
delta PositionMapping
acc in (PositionMapping
new, (PositionDelta
delta, PositionMapping
acc)))
PositionMapping
zeroMapping
(Int32
-> (PositionDelta, PositionMapping)
-> EnumMap Int32 (PositionDelta, PositionMapping)
-> EnumMap Int32 (PositionDelta, PositionMapping)
forall k a. Enum k => k -> a -> EnumMap k a -> EnumMap k a
EM.insert Int32
actual_version (PositionDelta
shared_change, PositionMapping
zeroMapping) EnumMap Int32 (PositionDelta, PositionMapping)
mappingForUri)
shared_change :: PositionDelta
shared_change = [TextDocumentContentChangeEvent] -> PositionDelta
mkDelta [TextDocumentContentChangeEvent]
changes
actual_version :: Int32
actual_version = case TextDocumentVersion
_version of
TextDocumentVersion
Nothing -> String -> Int32
forall a. HasCallStack => String -> a
error String
"Nothing version from server"
Just Int32
v -> Int32
v