Reimplement shake (continued) (#2060)

* Rewrite hls-graph to not use the Shake code

* redundant import

* Fix the bug

* add comments and format imports

* Fix another bug

* fix locking in incDatabase

* avoid calling withNumCapabilities on every build

* faster cleanup

* implement reverse deps

* --conservative-change-tracking

* Avoid grabbing the db lock when updating reverse deps

* update reverse deps asynchronously

* Profiling graph builds

* extend up profiling to record visiting steps

The main benefit of reverse dependency tracking is that we avoid unnecessary node lookups. However, these lookups were not shown in hls-graph profiles, hiding their real cost.

Concretely, if the number of lookups per build is proportional to the number of transitive dependencies of a node, which in turn is proportional to the number of transitive imports of a module, then we have an O(edges) complexity instead of an O(nodes) complexity, which is really bad for large projects.

This Diff extends the recorded data and the profiling UI to keep track
of visited nodes and to show them in a new column "Visited" of the "Rules" tab. The cost of doing this is storing an additional Int per node at runtime.

While I was editing the profiling UI, I took the chance to remove the command tabs, update the README and add some missing files

* include dirty set in profiles

* actionFork

* avoid spawning threads for simple lookups

* Fix a flaky test

* record changes to GetKnownTargets

* Readme for hls-graph

* Bump version numbers

* Drop dependency on Shake

* explain why we restart a Shake session

* clean up Internal.Database

* add a new benchmark example cabal-1module

* Fix masking and further reduce threading

* Trace aborted rule evaluations

* Fix code actions after cradle edit experiment

* Avoid spawning threads for build rules with 1 or fewer deps

* simplify a test

* hlint

* Add a test for off-editor changes

* Fix flaky tests

* fix incomplete pattern match in Tactics test suite

* Fix flaky tests

* attempt to fix tactics test suite in Windows

Co-authored-by: Neil Mitchell <ndmitchell@gmail.com>
This commit is contained in:
Pepe Iborra 2021-09-25 12:23:52 +02:00 committed by GitHub
parent c419b37db9
commit 682386d1c9
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
71 changed files with 8215 additions and 297 deletions

View File

@ -19,6 +19,19 @@ examples:
- Distribution/Simple.hs
- Distribution/Types/Module.hs
extra-args: [] # extra ghcide command line args
- name: cabal-1module
package: Cabal
version: 3.0.0.0
modules:
- Distribution/Simple.hs
- name: cabal-conservative
package: Cabal
version: 3.0.0.0
modules:
- Distribution/Simple.hs
- Distribution/Types/Module.hs
extra-args: # extra ghcide command line args
- --conservative-change-tracking
# Small-sized project with TH
- name: lsp-types
package: lsp-types
@ -26,7 +39,15 @@ examples:
modules:
- src/Language/LSP/VFS.hs
- src/Language/LSP/Types/Lens.hs
extra-args: [] # extra ghcide command line args
- name: lsp-types-conservative
package: lsp-types
version: 1.0.0.1
modules:
- src/Language/LSP/VFS.hs
- src/Language/LSP/Types/Lens.hs
extra-args:
- --conservative-change-tracking
# Small-sized project with TH
# Small but heavily multi-component example
# Disabled as it is far to slow. hie-bios >0.7.2 should help
# - name: HLS

View File

@ -152,21 +152,22 @@ experiments =
benchWithSetup
"code actions after cradle edit"
( \docs -> do
unless (any (isJust . identifierP) docs) $
error "None of the example modules is suitable for this experiment"
forM_ docs $ \DocumentPositions{..} ->
forM_ identifierP $ \p -> changeDoc doc [charEdit p]
forM_ docs $ \DocumentPositions{..} -> do
forM identifierP $ \p -> do
changeDoc doc [charEdit p]
waitForProgressStart
void waitForBuildQueue
)
( \docs -> do
hieYamlUri <- getDocUri "hie.yaml"
liftIO $ appendFile (fromJust $ uriToFilePath hieYamlUri) "##\n"
sendNotification SWorkspaceDidChangeWatchedFiles $ DidChangeWatchedFilesParams $
List [ FileEvent hieYamlUri FcChanged ]
forM_ docs $ \DocumentPositions{..} -> do
changeDoc doc [charEdit stringLiteralP]
waitForProgressStart
waitForProgressStart
waitForProgressStart
waitForProgressStart -- the Session logic restarts a second time
waitForProgressDone
not . null . catMaybes <$> forM docs (\DocumentPositions{..} -> do
not . all null . catMaybes <$> forM docs (\DocumentPositions{..} -> do
forM identifierP $ \p ->
getCodeActions doc (Range p p))
),
@ -421,6 +422,17 @@ waitForProgressDone = loop
done <- null <$> getIncompleteProgressSessions
unless done loop
-- | Wait for the build queue to be empty
waitForBuildQueue :: Session Seconds
waitForBuildQueue = do
let m = SCustomMethod "test"
waitId <- sendRequest m (toJSON WaitForShakeQueue)
(td, resp) <- duration $ skipManyTill anyMessage $ responseForId m waitId
case resp of
ResponseMessage{_result=Right Null} -> return td
-- assume a ghcide binary lacking the WaitForShakeQueue method
_ -> return 0
runBench ::
(?config :: Config) =>
(Session BenchRun -> IO BenchRun) ->
@ -451,15 +463,8 @@ runBench runSess b = handleAny (\e -> print e >> return badRun)
else do
output (showDuration t)
-- Wait for the delayed actions to finish
let m = SCustomMethod "test"
waitId <- sendRequest m (toJSON WaitForShakeQueue)
(td, resp) <- duration $ skipManyTill anyMessage $ responseForId m waitId
case resp of
ResponseMessage{_result=Right Null} -> do
loop (userWaits+t) (delayedWork+td) (n -1)
_ ->
-- Assume a ghcide build lacking the WaitForShakeQueue command
loop (userWaits+t) delayedWork (n -1)
td <- waitForBuildQueue
loop (userWaits+t) (delayedWork+td) (n -1)
(runExperiment, result) <- duration $ loop 0 0 samples
let success = isJust result

View File

@ -9,15 +9,16 @@ import Ide.Types (IdePlugins)
import Options.Applicative
data Arguments = Arguments
{argsCwd :: Maybe FilePath
,argsVersion :: Bool
,argsShakeProfiling :: Maybe FilePath
,argsOTMemoryProfiling :: Bool
,argsTesting :: Bool
,argsDisableKick :: Bool
,argsThreads :: Int
,argsVerbose :: Bool
,argsCommand :: Command
{argsCwd :: Maybe FilePath
,argsVersion :: Bool
,argsShakeProfiling :: Maybe FilePath
,argsOTMemoryProfiling :: Bool
,argsTesting :: Bool
,argsDisableKick :: Bool
,argsThreads :: Int
,argsVerbose :: Bool
,argsCommand :: Command
,argsConservativeChangeTracking :: Bool
}
getArguments :: IdePlugins IdeState -> IO Arguments
@ -38,6 +39,7 @@ arguments plugins = Arguments
<*> option auto (short 'j' <> help "Number of threads (0: automatic)" <> metavar "NUM" <> value 0 <> showDefault)
<*> switch (short 'd' <> long "verbose" <> help "Include internal events in logging output")
<*> (commandP plugins <|> lspCommand <|> checkCommand)
<*> switch (long "conservative-change-tracking" <> help "disable reactive change tracking (for testing/debugging)")
where
checkCommand = Check <$> many (argument str (metavar "FILES/DIRS..."))
lspCommand = LSP <$ flag' True (long "lsp" <> help "Start talking to an LSP client")

View File

@ -71,6 +71,8 @@ main = do
then Test.plugin
else mempty
,Main.argsThreads = case argsThreads of 0 -> Nothing ; i -> Just (fromIntegral i)
,Main.argsIdeOptions = \config sessionLoader ->
let defOptions = defaultIdeOptions sessionLoader
in defOptions
@ -80,5 +82,6 @@ main = do
, optShakeOptions = (optShakeOptions defOptions){shakeThreads = argsThreads}
, optCheckParents = pure $ checkParents config
, optCheckProject = pure $ checkProject config
, optRunSubset = not argsConservativeChangeTracking
}
}

View File

@ -48,6 +48,7 @@ library
dependent-map,
dependent-sum,
dlist,
exceptions,
-- we can't use >= 1.7.10 while we have to use hlint == 3.2.*
extra >= 1.7.4 && < 1.7.10,
fuzzy,
@ -76,7 +77,7 @@ library
rope-utf16-splay,
safe,
safe-exceptions,
hls-graph ^>= 1.4,
hls-graph ^>= 1.5,
sorted-list,
sqlite-simple,
stm,
@ -269,6 +270,7 @@ benchmark benchHist
directory,
extra,
filepath,
lens,
optparse-applicative,
shake,
text,

View File

@ -250,7 +250,6 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
IdeOptions{ optTesting = IdeTesting optTesting
, optCheckProject = getCheckProject
, optModifyDynFlags
, optExtensions
} <- getIdeOptions
@ -264,6 +263,7 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
TargetModule _ -> do
found <- filterM (IO.doesFileExist . fromNormalizedFilePath) targetLocations
return (targetTarget, found)
recordDirtyKeys extras GetKnownTargets [emptyFilePath]
modifyVarIO' knownTargetsVar $ traverseHashed $ \known -> do
let known' = HM.unionWith (<>) known $ HM.fromList $ map (second Set.fromList) knownTargets
when (known /= known') $
@ -390,7 +390,7 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
-- Invalidate all the existing GhcSession build nodes by restarting the Shake session
invalidateShakeCache
restartShakeSession []
restartShakeSession "new component" []
-- Typecheck all files in the project on startup
checkProject <- getCheckProject

View File

@ -48,7 +48,6 @@ import Development.IDE.Import.DependencyInformation
import Development.IDE.Types.Diagnostics
import Development.IDE.Types.Location
import Development.IDE.Types.Options
import Development.IDE.Types.Shake (SomeShakeValue)
import HieDb.Create (deleteMissingRealFiles)
import Ide.Plugin.Config (CheckParents (..),
Config)
@ -271,7 +270,7 @@ setFileModified state saved nfp = do
when (isJust setVirtualFileContents) $
fail "setFileModified can't be called on this type of VFSHandle"
recordDirtyKeys (shakeExtras state) GetModificationTime [nfp]
restartShakeSession (shakeExtras state) []
restartShakeSession (shakeExtras state) (fromNormalizedFilePath nfp ++ " (modified)") []
when checkParents $
typecheckParents state nfp
@ -294,8 +293,8 @@ typecheckParentsAction nfp = do
-- | Note that some keys have been modified and restart the session
-- Only valid if the virtual file system was initialised by LSP, as that
-- independently tracks which files are modified.
setSomethingModified :: IdeState -> [SomeShakeValue] -> IO ()
setSomethingModified state keys = do
setSomethingModified :: IdeState -> [Key] -> String -> IO ()
setSomethingModified state keys reason = do
VFSHandle{..} <- getIdeGlobalState state
when (isJust setVirtualFileContents) $
fail "setSomethingModified can't be called on this type of VFSHandle"
@ -303,7 +302,7 @@ setSomethingModified state keys = do
atomically $ writeTQueue (indexQueue $ hiedbWriter $ shakeExtras state) deleteMissingRealFiles
atomicModifyIORef_ (dirtyKeys $ shakeExtras state) $ \x ->
foldl' (flip HSet.insert) x keys
void $ restartShakeSession (shakeExtras state) []
void $ restartShakeSession (shakeExtras state) reason []
registerFileWatches :: [String] -> LSP.LspT Config IO Bool
registerFileWatches globs = do

View File

@ -18,7 +18,6 @@ module Development.IDE.Core.RuleTypes(
import Control.DeepSeq
import Control.Lens
import Data.Aeson.Types (Value)
import Data.Binary
import Data.Hashable
import qualified Data.Map as M
import Data.Time.Clock.POSIX
@ -76,7 +75,6 @@ data GetKnownTargets = GetKnownTargets
deriving (Show, Generic, Eq, Ord)
instance Hashable GetKnownTargets
instance NFData GetKnownTargets
instance Binary GetKnownTargets
type instance RuleResult GetKnownTargets = KnownTargets
-- | Convert to Core, requires TypeCheck*
@ -86,13 +84,11 @@ data GenerateCore = GenerateCore
deriving (Eq, Show, Typeable, Generic)
instance Hashable GenerateCore
instance NFData GenerateCore
instance Binary GenerateCore
data GetImportMap = GetImportMap
deriving (Eq, Show, Typeable, Generic)
instance Hashable GetImportMap
instance NFData GetImportMap
instance Binary GetImportMap
type instance RuleResult GetImportMap = ImportMap
newtype ImportMap = ImportMap
@ -281,7 +277,6 @@ instance Hashable GetModificationTime where
hashWithSalt salt _ = salt
instance NFData GetModificationTime
instance Binary GetModificationTime
pattern GetModificationTime :: GetModificationTime
pattern GetModificationTime = GetModificationTime_ {missingFileDiagnostics=True}
@ -304,14 +299,12 @@ data GetFileContents = GetFileContents
deriving (Eq, Show, Generic)
instance Hashable GetFileContents
instance NFData GetFileContents
instance Binary GetFileContents
data GetFileExists = GetFileExists
deriving (Eq, Show, Typeable, Generic)
instance NFData GetFileExists
instance Hashable GetFileExists
instance Binary GetFileExists
data FileOfInterestStatus
= OnDisk
@ -320,13 +313,11 @@ data FileOfInterestStatus
deriving (Eq, Show, Typeable, Generic)
instance Hashable FileOfInterestStatus
instance NFData FileOfInterestStatus
instance Binary FileOfInterestStatus
data IsFileOfInterestResult = NotFOI | IsFOI FileOfInterestStatus
deriving (Eq, Show, Typeable, Generic)
instance Hashable IsFileOfInterestResult
instance NFData IsFileOfInterestResult
instance Binary IsFileOfInterestResult
type instance RuleResult IsFileOfInterest = IsFileOfInterestResult
@ -353,19 +344,16 @@ data GetParsedModule = GetParsedModule
deriving (Eq, Show, Typeable, Generic)
instance Hashable GetParsedModule
instance NFData GetParsedModule
instance Binary GetParsedModule
data GetParsedModuleWithComments = GetParsedModuleWithComments
deriving (Eq, Show, Typeable, Generic)
instance Hashable GetParsedModuleWithComments
instance NFData GetParsedModuleWithComments
instance Binary GetParsedModuleWithComments
data GetLocatedImports = GetLocatedImports
deriving (Eq, Show, Typeable, Generic)
instance Hashable GetLocatedImports
instance NFData GetLocatedImports
instance Binary GetLocatedImports
-- | Does this module need to be compiled?
type instance RuleResult NeedsCompilation = Maybe LinkableType
@ -374,122 +362,102 @@ data NeedsCompilation = NeedsCompilation
deriving (Eq, Show, Typeable, Generic)
instance Hashable NeedsCompilation
instance NFData NeedsCompilation
instance Binary NeedsCompilation
data GetDependencyInformation = GetDependencyInformation
deriving (Eq, Show, Typeable, Generic)
instance Hashable GetDependencyInformation
instance NFData GetDependencyInformation
instance Binary GetDependencyInformation
data GetModuleGraph = GetModuleGraph
deriving (Eq, Show, Typeable, Generic)
instance Hashable GetModuleGraph
instance NFData GetModuleGraph
instance Binary GetModuleGraph
data ReportImportCycles = ReportImportCycles
deriving (Eq, Show, Typeable, Generic)
instance Hashable ReportImportCycles
instance NFData ReportImportCycles
instance Binary ReportImportCycles
data GetDependencies = GetDependencies
deriving (Eq, Show, Typeable, Generic)
instance Hashable GetDependencies
instance NFData GetDependencies
instance Binary GetDependencies
data TypeCheck = TypeCheck
deriving (Eq, Show, Typeable, Generic)
instance Hashable TypeCheck
instance NFData TypeCheck
instance Binary TypeCheck
data GetDocMap = GetDocMap
deriving (Eq, Show, Typeable, Generic)
instance Hashable GetDocMap
instance NFData GetDocMap
instance Binary GetDocMap
data GetHieAst = GetHieAst
deriving (Eq, Show, Typeable, Generic)
instance Hashable GetHieAst
instance NFData GetHieAst
instance Binary GetHieAst
data GetBindings = GetBindings
deriving (Eq, Show, Typeable, Generic)
instance Hashable GetBindings
instance NFData GetBindings
instance Binary GetBindings
data GhcSession = GhcSession
deriving (Eq, Show, Typeable, Generic)
instance Hashable GhcSession
instance NFData GhcSession
instance Binary GhcSession
data GhcSessionDeps = GhcSessionDeps deriving (Eq, Show, Typeable, Generic)
instance Hashable GhcSessionDeps
instance NFData GhcSessionDeps
instance Binary GhcSessionDeps
data GetModIfaceFromDisk = GetModIfaceFromDisk
deriving (Eq, Show, Typeable, Generic)
instance Hashable GetModIfaceFromDisk
instance NFData GetModIfaceFromDisk
instance Binary GetModIfaceFromDisk
data GetModIfaceFromDiskAndIndex = GetModIfaceFromDiskAndIndex
deriving (Eq, Show, Typeable, Generic)
instance Hashable GetModIfaceFromDiskAndIndex
instance NFData GetModIfaceFromDiskAndIndex
instance Binary GetModIfaceFromDiskAndIndex
data GetModIface = GetModIface
deriving (Eq, Show, Typeable, Generic)
instance Hashable GetModIface
instance NFData GetModIface
instance Binary GetModIface
data GetModIfaceWithoutLinkable = GetModIfaceWithoutLinkable
deriving (Eq, Show, Typeable, Generic)
instance Hashable GetModIfaceWithoutLinkable
instance NFData GetModIfaceWithoutLinkable
instance Binary GetModIfaceWithoutLinkable
data IsFileOfInterest = IsFileOfInterest
deriving (Eq, Show, Typeable, Generic)
instance Hashable IsFileOfInterest
instance NFData IsFileOfInterest
instance Binary IsFileOfInterest
data GetModSummaryWithoutTimestamps = GetModSummaryWithoutTimestamps
deriving (Eq, Show, Typeable, Generic)
instance Hashable GetModSummaryWithoutTimestamps
instance NFData GetModSummaryWithoutTimestamps
instance Binary GetModSummaryWithoutTimestamps
data GetModSummary = GetModSummary
deriving (Eq, Show, Typeable, Generic)
instance Hashable GetModSummary
instance NFData GetModSummary
instance Binary GetModSummary
-- | Get the vscode client settings stored in the ide state
data GetClientSettings = GetClientSettings
deriving (Eq, Show, Typeable, Generic)
instance Hashable GetClientSettings
instance NFData GetClientSettings
instance Binary GetClientSettings
type instance RuleResult GetClientSettings = Hashed (Maybe Value)
data AddWatchedFile = AddWatchedFile deriving (Eq, Show, Typeable, Generic)
instance Hashable AddWatchedFile
instance NFData AddWatchedFile
instance Binary AddWatchedFile
-- A local rule type to get caching. We want to use newCache, but it has
@ -510,7 +478,6 @@ instance NFData IdeGhcSession where rnf !_ = ()
data GhcSessionIO = GhcSessionIO deriving (Eq, Show, Typeable, Generic)
instance Hashable GhcSessionIO
instance NFData GhcSessionIO
instance Binary GhcSessionIO
makeLensesWith
(lensRules & lensField .~ mappingNamer (pure . (++ "L")))

View File

@ -73,7 +73,6 @@ import Control.Monad.Trans.Maybe
import Data.Aeson (Result (Success),
toJSON)
import qualified Data.Aeson.Types as A
import Data.Binary hiding (get, put)
import qualified Data.Binary as B
import qualified Data.ByteString as BS
import Data.ByteString.Encoding as T
@ -119,7 +118,7 @@ import Development.IDE.GHC.ExactPrint
import Development.IDE.GHC.Util hiding
(modifyDynFlags)
import Development.IDE.Graph
import Development.IDE.Graph.Classes hiding (get, put)
import Development.IDE.Graph.Classes
import Development.IDE.Import.DependencyInformation
import Development.IDE.Import.FindImports
import qualified Development.IDE.Spans.AtPoint as AtPoint
@ -1090,6 +1089,5 @@ data IsHiFileStable = IsHiFileStable
deriving (Eq, Show, Typeable, Generic)
instance Hashable IsHiFileStable
instance NFData IsHiFileStable
instance Binary IsHiFileStable
type instance RuleResult IsHiFileStable = SourceModified

View File

@ -117,7 +117,6 @@ import Development.IDE.GHC.Compat (NameCacheUpdater (..),
import Development.IDE.GHC.Orphans ()
import Development.IDE.Graph hiding (ShakeValue)
import qualified Development.IDE.Graph as Shake
import Development.IDE.Graph.Classes
import Development.IDE.Graph.Database
import Development.IDE.Graph.Rule
import Development.IDE.Types.Action
@ -195,7 +194,8 @@ data ShakeExtras = ShakeExtras
,ideTesting :: IdeTesting
-- ^ Whether to enable additional lsp messages used by the test suite for checking invariants
,restartShakeSession
:: [DelayedAction ()]
:: String
-> [DelayedAction ()]
-> IO ()
,ideNc :: IORef NameCache
-- | A mapping of module name to known target (or candidate targets, if missing)
@ -213,7 +213,7 @@ data ShakeExtras = ShakeExtras
, vfs :: VFSHandle
, defaultConfig :: Config
-- ^ Default HLS config, only relevant if the client does not provide any Config
, dirtyKeys :: IORef (HashSet SomeShakeValue)
, dirtyKeys :: IORef (HashSet Key)
-- ^ Set of dirty rule keys since the last Shake run
}
@ -584,8 +584,8 @@ delayedAction a = do
-- | Restart the current 'ShakeSession' with the given system actions.
-- Any actions running in the current session will be aborted,
-- but actions added via 'shakeEnqueue' will be requeued.
shakeRestart :: IdeState -> [DelayedAction ()] -> IO ()
shakeRestart IdeState{..} acts =
shakeRestart :: IdeState -> String -> [DelayedAction ()] -> IO ()
shakeRestart IdeState{..} reason acts =
withMVar'
shakeSession
(\runner -> do
@ -595,8 +595,9 @@ shakeRestart IdeState{..} acts =
let profile = case res of
Just fp -> ", profile saved at " <> fp
_ -> ""
let msg = T.pack $ "Restarting build session " ++ keysMsg ++ abortMsg
keysMsg = "for keys " ++ show (HSet.toList backlog) ++ " "
let msg = T.pack $ "Restarting build session " ++ reason' ++ keysMsg ++ abortMsg
reason' = "due to " ++ reason
keysMsg = " for keys " ++ show (HSet.toList backlog) ++ " "
abortMsg = "(aborting the previous one took " ++ showDuration stopTime ++ profile ++ ")"
logDebug (logger shakeExtras) msg
notifyTestingLogMessage shakeExtras msg
@ -655,7 +656,7 @@ newSession extras@ShakeExtras{..} shakeDb acts = do
-- Runs actions from the work queue sequentially
pumpActionThread otSpan = do
d <- liftIO $ atomically $ popQueue actionQueue
void $ parallel [run otSpan d, pumpActionThread otSpan]
actionFork (run otSpan d) $ \_ -> pumpActionThread otSpan
-- TODO figure out how to thread the otSpan into defineEarlyCutoff
run _otSpan d = do
@ -871,9 +872,9 @@ defineEarlyCutoff
:: IdeRule k v
=> RuleBody k v
-> Rules ()
defineEarlyCutoff (Rule op) = addRule $ \(Q (key, file)) (old :: Maybe BS.ByteString) mode -> otTracedAction key file mode isSuccess $ do
defineEarlyCutoff (Rule op) = addRule $ \(Q (key, file)) (old :: Maybe BS.ByteString) mode -> otTracedAction key file mode traceA $ do
defineEarlyCutoff' True key file old mode $ op key file
defineEarlyCutoff (RuleNoDiagnostics op) = addRule $ \(Q (key, file)) (old :: Maybe BS.ByteString) mode -> otTracedAction key file mode isSuccess $ do
defineEarlyCutoff (RuleNoDiagnostics op) = addRule $ \(Q (key, file)) (old :: Maybe BS.ByteString) mode -> otTracedAction key file mode traceA $ do
defineEarlyCutoff' False key file old mode $ second (mempty,) <$> op key file
defineNoFile :: IdeRule k v => (k -> Action v) -> Rules ()
@ -916,7 +917,8 @@ defineEarlyCutoff' doDiagnostics key file old mode action = do
Nothing -> do
(bs, (diags, res)) <- actionCatch
(do v <- action; liftIO $ evaluate $ force v) $
\(e :: SomeException) -> pure (Nothing, ([ideErrorText file $ T.pack $ show e | not $ isBadDependency e],Nothing))
\(e :: SomeException) -> do
pure (Nothing, ([ideErrorText file $ T.pack $ show e | not $ isBadDependency e],Nothing))
modTime <- liftIO $ (currentValue . fst =<<) <$> getValues state GetModificationTime file
(bs, res) <- case res of
Nothing -> do
@ -948,9 +950,10 @@ defineEarlyCutoff' doDiagnostics key file old mode action = do
liftIO $ atomicModifyIORef'_ dirtyKeys (HSet.delete $ toKey key file)
return res
isSuccess :: A v -> Bool
isSuccess (A Failed{}) = False
isSuccess _ = True
traceA :: A v -> String
traceA (A Failed{}) = "Failed"
traceA (A Stale{}) = "Stale"
traceA (A Succeeded{}) = "Success"
-- | Rule type, input file
data QDisk k = QDisk k NormalizedFilePath
@ -960,8 +963,6 @@ instance Hashable k => Hashable (QDisk k)
instance NFData k => NFData (QDisk k)
instance Binary k => Binary (QDisk k)
instance Show k => Show (QDisk k) where
show (QDisk k file) =
show k ++ "; " ++ fromNormalizedFilePath file

View File

@ -15,15 +15,18 @@ import Control.Concurrent.Async (Async, async)
import Control.Concurrent.Extra (Var, modifyVar_, newVar,
readVar, threadDelay)
import Control.Exception (evaluate)
import Control.Exception.Safe (SomeException, catch)
import Control.Monad (forM_, forever, unless, void,
when, (>=>))
import Control.Exception.Safe (SomeException, catch,
generalBracket)
import Control.Monad (forM_, forever, void, when,
(>=>))
import Control.Monad.Catch (ExitCase (..))
import Control.Monad.Extra (whenJust)
import Control.Monad.IO.Unlift
import Control.Seq (r0, seqList, seqTuple2, using)
#if MIN_VERSION_ghc(8,8,0)
import Data.ByteString (ByteString)
#endif
import Data.ByteString.Char8 (pack)
import Data.Dynamic (Dynamic)
import qualified Data.HashMap.Strict as HMap
import Data.IORef (modifyIORef', newIORef,
@ -34,7 +37,7 @@ import Debug.Trace.Flags (userTracingEnabled)
import Development.IDE.Core.RuleTypes (GhcSession (GhcSession),
GhcSessionDeps (GhcSessionDeps),
GhcSessionIO (GhcSessionIO))
import Development.IDE.Graph (Action, actionBracket)
import Development.IDE.Graph (Action)
import Development.IDE.Graph.Rule
import Development.IDE.Types.Location (Uri (..))
import Development.IDE.Types.Logger (Logger, logDebug, logInfo)
@ -81,25 +84,28 @@ otTracedAction
=> k -- ^ The Action's Key
-> NormalizedFilePath -- ^ Path to the file the action was run for
-> RunMode
-> (a -> Bool)
-> (a -> String)
-> Action (RunResult a) -- ^ The action
-> Action (RunResult a)
otTracedAction key file mode success act
| userTracingEnabled =
actionBracket
otTracedAction key file mode result act
| userTracingEnabled = fst <$>
generalBracket
(do
sp <- beginSpan (fromString (show key))
setTag sp "File" (fromString $ fromNormalizedFilePath file)
setTag sp "Mode" (fromString $ show mode)
return sp
)
endSpan
(\sp -> do
res <- act
unless (success $ runValue res) $ setTag sp "error" "1"
setTag sp "changed" $ case res of
RunResult x _ _ -> fromString $ show x
return res)
(\sp ec -> do
case ec of
ExitCaseAbort -> setTag sp "aborted" "1"
ExitCaseException e -> setTag sp "exception" (pack $ show e)
ExitCaseSuccess res -> do
setTag sp "result" (pack $ result $ runValue res)
setTag sp "changed" $ case res of
RunResult x _ _ -> fromString $ show x
endSpan sp)
(const act)
| otherwise = act
#if MIN_VERSION_ghc(8,8,0)

View File

@ -81,7 +81,6 @@ data GetAnnotatedParsedSource = GetAnnotatedParsedSource
instance Hashable GetAnnotatedParsedSource
instance NFData GetAnnotatedParsedSource
instance Binary GetAnnotatedParsedSource
type instance RuleResult GetAnnotatedParsedSource = Annotated ParsedSource
-- | Get the latest version of the annotated parse source with comments.

View File

@ -82,11 +82,11 @@ descriptor plId = (defaultPluginDescriptor plId) { pluginNotificationHandlers =
\ide _ (DidChangeWatchedFilesParams (List fileEvents)) -> liftIO $ do
-- See Note [File existence cache and LSP file watchers] which explains why we get these notifications and
-- what we do with them
let msg = Text.pack $ show fileEvents
logDebug (ideLogger ide) $ "Watched file events: " <> msg
let msg = show fileEvents
logDebug (ideLogger ide) $ "Watched file events: " <> Text.pack msg
modifyFileExists ide fileEvents
resetFileStore ide fileEvents
setSomethingModified ide []
setSomethingModified ide [] msg
, mkPluginNotificationHandler LSP.SWorkspaceDidChangeWorkspaceFolders $
\ide _ (DidChangeWorkspaceFoldersParams events) -> liftIO $ do
@ -101,7 +101,7 @@ descriptor plId = (defaultPluginDescriptor plId) { pluginNotificationHandlers =
let msg = Text.pack $ show cfg
logDebug (ideLogger ide) $ "Configuration changed: " <> msg
modifyClientSettings ide (const $ Just cfg)
setSomethingModified ide [toKey GetClientSettings emptyFilePath ]
setSomethingModified ide [toKey GetClientSettings emptyFilePath] "config change"
, mkPluginNotificationHandler LSP.SInitialized $ \ide _ _ -> do
--------- Initialize Shake session --------------------------------------------------------------------

View File

@ -8,7 +8,8 @@ module Development.IDE.Main
,defaultMain
) where
import Control.Concurrent.Extra (newLock, readVar,
withLock)
withLock,
withNumCapabilities)
import Control.Exception.Safe (Exception (displayException),
catchAny)
import Control.Monad.Extra (concatMapM, unless,
@ -68,6 +69,7 @@ import Development.IDE.Types.Options (IdeGhcSession,
defaultIdeOptions,
optModifyDynFlags)
import Development.IDE.Types.Shake (Key (Key))
import GHC.Conc (getNumProcessors)
import GHC.IO.Encoding (setLocaleEncoding)
import GHC.IO.Handle (hDuplicate)
import HIE.Bios.Cradle (findCradle)
@ -86,6 +88,7 @@ import Ide.Types (IdeCommand (IdeCommand),
PluginId (PluginId),
ipMap)
import qualified Language.LSP.Server as LSP
import Numeric.Natural (Natural)
import Options.Applicative hiding (action)
import qualified System.Directory.Extra as IO
import System.Exit (ExitCode (ExitFailure),
@ -163,6 +166,7 @@ data Arguments = Arguments
, argsDebouncer :: IO (Debouncer NormalizedUri) -- ^ Debouncer used for diagnostics
, argsHandleIn :: IO Handle
, argsHandleOut :: IO Handle
, argsThreads :: Maybe Natural
}
instance Default Arguments where
@ -179,6 +183,7 @@ instance Default Arguments where
, argsDefaultHlsConfig = def
, argsGetHieDbLoc = getHieDbLoc
, argsDebouncer = newAsyncDebouncer
, argsThreads = Nothing
, argsHandleIn = pure stdin
, argsHandleOut = do
-- Move stdout to another file descriptor and duplicate stderr
@ -221,12 +226,14 @@ defaultMain Arguments{..} = do
inH <- argsHandleIn
outH <- argsHandleOut
numProcessors <- getNumProcessors
case argCommand of
PrintExtensionSchema ->
LT.putStrLn $ decodeUtf8 $ A.encodePretty $ pluginsToVSCodeExtensionSchema argsHlsPlugins
PrintDefaultConfig ->
LT.putStrLn $ decodeUtf8 $ A.encodePretty $ pluginsToDefaultConfig argsHlsPlugins
LSP -> do
LSP -> withNumCapabilities (maybe (numProcessors `div` 2) fromIntegral argsThreads) $ do
t <- offsetTime
hPutStrLn stderr "Starting LSP server..."
hPutStrLn stderr "If you are seeing this in a terminal, you probably should have run WITHOUT the --lsp option!"
@ -250,6 +257,7 @@ defaultMain Arguments{..} = do
-- disable runSubset if the client doesn't support watched files
runSubset <- (optRunSubset def_options &&) <$> LSP.runLspT env isWatchSupported
hPutStrLn stderr $ "runSubset: " <> show runSubset
let options = def_options
{ optReportProgress = clientSupportsProgress caps

View File

@ -5,7 +5,6 @@ module Development.IDE.Plugin.CodeAction.RuleTypes
) where
import Control.DeepSeq (NFData)
import Data.Binary (Binary)
import Data.Hashable (Hashable)
import Data.Typeable (Typeable)
import Development.IDE.Graph (RuleResult)
@ -21,4 +20,3 @@ newtype PackageExports = PackageExports HscEnvEq
instance Hashable PackageExports
instance NFData PackageExports
instance Binary PackageExports

View File

@ -105,13 +105,11 @@ data LocalCompletions = LocalCompletions
deriving (Eq, Show, Typeable, Generic)
instance Hashable LocalCompletions
instance NFData LocalCompletions
instance Binary LocalCompletions
data NonLocalCompletions = NonLocalCompletions
deriving (Eq, Show, Typeable, Generic)
instance Hashable NonLocalCompletions
instance NFData NonLocalCompletions
instance Binary NonLocalCompletions
-- | Generate code actions.
getCompletionsLSP

View File

@ -215,7 +215,7 @@ showDocRdrEnv :: HscEnv -> GlobalRdrEnv -> SDoc -> String
showDocRdrEnv env rdrEnv = showSDocForUser (hsc_dflags env) (mkPrintUnqualified (hsc_dflags env) rdrEnv)
data GetGlobalBindingTypeSigs = GetGlobalBindingTypeSigs
deriving (Generic, Show, Eq, Ord, Hashable, NFData, Binary)
deriving (Generic, Show, Eq, Ord, Hashable, NFData)
data GlobalBindingTypeSig = GlobalBindingTypeSig
{ gbName :: Name

View File

@ -135,12 +135,6 @@ instance NFData HscEnvEq where
instance Hashable HscEnvEq where
hashWithSalt s = hashWithSalt s . envUnique
-- Fake instance needed to persuade Shake to accept this type as a key.
-- No harm done as ghcide never persists these keys currently
instance Binary HscEnvEq where
put _ = error "not really"
get = error "not really"
-- | Given an action, produce a wrapped action that runs at most once.
-- The action is run in an async so it won't be killed by async exceptions
-- If the function raises an exception, the same exception will be reraised each time.

View File

@ -142,7 +142,7 @@ defaultIdeOptions session = IdeOptions
,optModifyDynFlags = mempty
,optSkipProgress = defaultSkipProgress
,optProgressStyle = Explicit
,optRunSubset = False
,optRunSubset = True
}
defaultSkipProgress :: Typeable a => a -> Bool

View File

@ -8,7 +8,6 @@ module Development.IDE.Types.Shake
ValueWithDiagnostics (..),
Values,
Key (..),
SomeShakeValue,
BadDependency (..),
ShakeValue(..),
currentValue,
@ -22,14 +21,10 @@ import qualified Data.ByteString.Char8 as BS
import Data.Dynamic
import Data.HashMap.Strict
import Data.Hashable
import Data.Typeable
import Data.Vector (Vector)
import Development.IDE.Core.PositionMapping
import Development.IDE.Graph (RuleResult,
ShakeException (shakeExceptionInner))
import Development.IDE.Graph (Key (..), RuleResult)
import qualified Development.IDE.Graph as Shake
import Development.IDE.Graph.Classes
import Development.IDE.Graph.Database (SomeShakeValue (..))
import Development.IDE.Types.Diagnostics
import Development.IDE.Types.Location
import GHC.Generics
@ -56,26 +51,6 @@ data ValueWithDiagnostics
-- | The state of the all values and diagnostics
type Values = HashMap (NormalizedFilePath, Key) ValueWithDiagnostics
-- | Key type
data Key = forall k . (Typeable k, Hashable k, Eq k, NFData k, Show k) => Key k
instance Show Key where
show (Key k) = show k
instance Eq Key where
Key k1 == Key k2 | Just k2' <- cast k2 = k1 == k2'
| otherwise = False
instance Hashable Key where
hashWithSalt salt (Key key) = hashWithSalt salt key
instance Binary Key where
get = error "not really"
put _ = error "not really"
instance NFData Key where
rnf (Key k) = rnf k
-- | When we depend on something that reported an error, and we fail as a direct result, throw BadDependency
-- which short-circuits the rest of the action
newtype BadDependency = BadDependency String deriving Show
@ -83,29 +58,18 @@ instance Exception BadDependency
isBadDependency :: SomeException -> Bool
isBadDependency x
| Just (x :: ShakeException) <- fromException x = isBadDependency $ shakeExceptionInner x
| Just (_ :: BadDependency) <- fromException x = True
| otherwise = False
toKey :: Shake.ShakeValue k => k -> NormalizedFilePath -> Key
toKey = (Key.) . curry Q
toKey :: Shake.ShakeValue k => k -> NormalizedFilePath -> SomeShakeValue
toKey = (SomeShakeValue .) . curry Q
toNoFileKey :: (Show k, Typeable k, Eq k, Hashable k, Binary k, NFData k) => k -> SomeShakeValue
toNoFileKey k = toKey k emptyFilePath
toNoFileKey :: (Show k, Typeable k, Eq k, Hashable k) => k -> Key
toNoFileKey k = Key $ Q (k, emptyFilePath)
newtype Q k = Q (k, NormalizedFilePath)
deriving newtype (Eq, Hashable, NFData)
instance Binary k => Binary (Q k) where
put (Q (k, fp)) = put (k, fp)
get = do
(k, fp) <- get
-- The `get` implementation of NormalizedFilePath
-- does not handle empty file paths so we
-- need to handle this ourselves here.
pure (Q (k, toNormalizedFilePath' fp))
instance Show k => Show (Q k) where
show (Q (k, file)) = show k ++ "; " ++ fromNormalizedFilePath file

View File

@ -21,7 +21,6 @@ import Control.Monad
import Control.Monad.IO.Class (MonadIO, liftIO)
import Data.Aeson (fromJSON, toJSON)
import qualified Data.Aeson as A
import qualified Data.Binary as Binary
import Data.Default
import Data.Foldable
import Data.List.Extra
@ -34,7 +33,6 @@ import Development.IDE.Core.PositionMapping (PositionResult (..),
fromCurrent,
positionResultToMaybe,
toCurrent)
import Development.IDE.Core.Shake (Q (..))
import Development.IDE.GHC.Compat (GhcVersion (..),
ghcVersion)
import Development.IDE.GHC.Util
@ -124,6 +122,17 @@ waitForProgressDone = skipManyTill anyMessage $ satisfyMaybe $ \case
FromServerMess SProgress (NotificationMessage _ _ (ProgressParams _ (End _))) -> Just ()
_ -> Nothing
-- | Wait for all progress to be done
-- Needs at least one progress done notification to return
waitForAllProgressDone :: Session ()
waitForAllProgressDone = loop
where
loop = do
~() <- skipManyTill anyMessage $ satisfyMaybe $ \case
FromServerMess SProgress (NotificationMessage _ _ (ProgressParams _ (End _))) -> Just ()
_ -> Nothing
done <- null <$> getIncompleteProgressSessions
unless done loop
main :: IO ()
main = do
-- We mess with env vars so run single-threaded.
@ -770,25 +779,51 @@ codeLensesTests = testGroup "code lenses"
watchedFilesTests :: TestTree
watchedFilesTests = testGroup "watched files"
[ testSession' "workspace files" $ \sessionDir -> do
liftIO $ writeFile (sessionDir </> "hie.yaml") "cradle: {direct: {arguments: [\"-isrc\", \"A\", \"WatchedFilesMissingModule\"]}}"
_doc <- createDoc "A.hs" "haskell" "{-#LANGUAGE NoImplicitPrelude #-}\nmodule A where\nimport WatchedFilesMissingModule"
watchedFileRegs <- getWatchedFilesSubscriptionsUntil STextDocumentPublishDiagnostics
[ testGroup "Subscriptions"
[ testSession' "workspace files" $ \sessionDir -> do
liftIO $ writeFile (sessionDir </> "hie.yaml") "cradle: {direct: {arguments: [\"-isrc\", \"A\", \"WatchedFilesMissingModule\"]}}"
_doc <- createDoc "A.hs" "haskell" "{-#LANGUAGE NoImplicitPrelude #-}\nmodule A where\nimport WatchedFilesMissingModule"
watchedFileRegs <- getWatchedFilesSubscriptionsUntil STextDocumentPublishDiagnostics
-- Expect 2 subscriptions: one for all .hs files and one for the hie.yaml cradle
liftIO $ length watchedFileRegs @?= 2
-- Expect 2 subscriptions: one for all .hs files and one for the hie.yaml cradle
liftIO $ length watchedFileRegs @?= 2
, testSession' "non workspace file" $ \sessionDir -> do
tmpDir <- liftIO getTemporaryDirectory
let yaml = "cradle: {direct: {arguments: [\"-i" <> tail(init(show tmpDir)) <> "\", \"A\", \"WatchedFilesMissingModule\"]}}"
liftIO $ writeFile (sessionDir </> "hie.yaml") yaml
_doc <- createDoc "A.hs" "haskell" "{-# LANGUAGE NoImplicitPrelude#-}\nmodule A where\nimport WatchedFilesMissingModule"
watchedFileRegs <- getWatchedFilesSubscriptionsUntil STextDocumentPublishDiagnostics
, testSession' "non workspace file" $ \sessionDir -> do
tmpDir <- liftIO getTemporaryDirectory
let yaml = "cradle: {direct: {arguments: [\"-i" <> tail(init(show tmpDir)) <> "\", \"A\", \"WatchedFilesMissingModule\"]}}"
liftIO $ writeFile (sessionDir </> "hie.yaml") yaml
_doc <- createDoc "A.hs" "haskell" "{-# LANGUAGE NoImplicitPrelude#-}\nmodule A where\nimport WatchedFilesMissingModule"
watchedFileRegs <- getWatchedFilesSubscriptionsUntil STextDocumentPublishDiagnostics
-- Expect 2 subscriptions: one for all .hs files and one for the hie.yaml cradle
liftIO $ length watchedFileRegs @?= 2
-- Expect 2 subscriptions: one for all .hs files and one for the hie.yaml cradle
liftIO $ length watchedFileRegs @?= 2
-- TODO add a test for didChangeWorkspaceFolder
-- TODO add a test for didChangeWorkspaceFolder
]
, testGroup "Changes"
[
testSession' "workspace files" $ \sessionDir -> do
liftIO $ writeFile (sessionDir </> "hie.yaml") "cradle: {direct: {arguments: [\"-isrc\", \"A\", \"B\"]}}"
liftIO $ writeFile (sessionDir </> "B.hs") $ unlines
["module B where"
,"b :: Bool"
,"b = False"]
_doc <- createDoc "A.hs" "haskell" $ T.unlines
["module A where"
,"import B"
,"a :: ()"
,"a = b"
]
expectDiagnostics [("A.hs", [(DsError, (3, 4), "Couldn't match expected type '()' with actual type 'Bool'")])]
-- modify B off editor
liftIO $ writeFile (sessionDir </> "B.hs") $ unlines
["module B where"
,"b :: Int"
,"b = 0"]
sendNotification SWorkspaceDidChangeWatchedFiles $ DidChangeWatchedFilesParams $
List [FileEvent (filePathToUri $ sessionDir </> "B.hs") FcChanged ]
expectDiagnostics [("A.hs", [(DsError, (3, 4), "Couldn't match expected type '()' with actual type 'Int'")])]
]
]
insertImportTests :: TestTree
@ -4043,8 +4078,10 @@ thLinkingTest unboxed = testCase name $ runWithExtraFiles dir $ \dir -> do
-- modify b too
let bSource' = T.unlines $ init (T.lines bSource) ++ ["$th"]
changeDoc bdoc [TextDocumentContentChangeEvent Nothing Nothing bSource']
waitForProgressBegin
waitForAllProgressDone
expectDiagnostics [("THB.hs", [(DsWarning, (4,thDollarIdx), "Top-level binding")])]
expectCurrentDiagnostics bdoc [(DsWarning, (4,thDollarIdx), "Top-level binding")]
closeDoc adoc
closeDoc bdoc
@ -5005,15 +5042,6 @@ retryFailedCradle = testSession' "retry failed" $ \dir -> do
liftIO $ writeFileUTF8 hiePath $ T.unpack validCradle
sendNotification SWorkspaceDidChangeWatchedFiles $ DidChangeWatchedFilesParams $
List [FileEvent (filePathToUri $ dir </> "hie.yaml") FcChanged ]
-- Force a session restart by making an edit, just to dirty the typecheck node
changeDoc
doc
[ TextDocumentContentChangeEvent
{ _range = Just Range {_start = Position 0 0, _end = Position 0 0},
_rangeLength = Nothing,
_text = "\n"
}
]
Right WaitForIdeRuleResult {..} <- waitForAction "TypeCheck" doc
liftIO $ "No joy after fixing the cradle" `assertBool` ideResultSuccess
@ -5765,8 +5793,6 @@ unitTests = do
, testCase "from empty path URI" $ do
let uri = Uri "file://"
uriToFilePath' uri @?= Just ""
, testCase "Key with empty file path roundtrips via Binary" $
Binary.decode (Binary.encode (Q ((), emptyFilePath))) @?= Q ((), emptyFilePath)
, testCase "showDiagnostics prints ranges 1-based (like vscode)" $ do
let diag = ("", Diagnostics.ShowDiag, Diagnostic
{ _range = Range

17
hls-graph/README.md Normal file
View File

@ -0,0 +1,17 @@
# hls-graph - a limited reimplementation of Shake for in-memory build graphs
`ghcide` was originally built on top of [Shake](http://shakebuild.com), a Haskell build system. Nowadays Shake has been replaced by a special purpose implementation of a build graph called hls-graph, which drops all the persistency features in exchange for simplicity and performance.
Features:
* Dynamic dependencies
* User defined rules (there are no predefined File rules as in Shake)
* Build reports (a la Shake profiling)
* "Reactive" change tracking for minimal rebuilds (not available in Shake)
What's missing:
* Persistence
* A default set of rules for file system builds
* A testsuite
* General purpose application - many design decisions make assumptions specific to ghcide

View File

@ -1,6 +1,6 @@
cabal-version: 2.4
name: hls-graph
version: 1.4.0.0
version: 1.5.0.0
synopsis: Haskell Language Server internal graph API
description:
Please see the README on GitHub at <https://github.com/haskell/haskell-language-server#readme>
@ -14,12 +14,20 @@ maintainer: alan.zimm@gmail.com
copyright: The Haskell IDE Team
category: Development
build-type: Simple
data-files:
html/profile.html
html/shake.js
flag pedantic
description: Enable -Werror
default: False
manual: True
flag embed-files
default: False
manual: True
description: Embed data files into the shake library
source-repository head
type: git
location: https://github.com/haskell/haskell-language-server
@ -35,14 +43,42 @@ library
Development.IDE.Graph.Internal.Action
Development.IDE.Graph.Internal.Options
Development.IDE.Graph.Internal.Rules
Development.IDE.Graph.Internal.Database
Development.IDE.Graph.Internal.Ids
Development.IDE.Graph.Internal.Intern
Development.IDE.Graph.Internal.Paths
Development.IDE.Graph.Internal.Profile
Development.IDE.Graph.Internal.Types
Paths_hls_graph
autogen-modules: Paths_hls_graph
hs-source-dirs: src
build-depends:
, async
, base >=4.12 && <5
, bytestring
, shake >= 0.19.4
, containers
, deepseq
, directory
, exceptions
, extra
, filepath
, hashable
, js-dgtable
, js-flot
, js-jquery
, primitive
, time
, transformers
, unordered-containers
if flag(embed-files)
cpp-options: -DFILE_EMBED
build-depends:
file-embed >= 0.0.11,
template-haskell
ghc-options:
-Wall -Wredundant-constraints -Wno-name-shadowing
-Wno-unticked-promoted-constructors

24
hls-graph/html/README.md Normal file
View File

@ -0,0 +1,24 @@
# Shake HTML
HTML files originally used by Shake and now by hls-graph, for profiling build runs.
## Files
* `profile.html` is the actual profiler.
* `profile-data.js`, `progress-data.js` and `metadata.js` are files with sample data, matching that generated by the compiler.
* `shake.js` is generated from the code in `ts`.
## Development
Before doing any work you need the jQuery, Flot and dgtable JavaScript dependencies. These can be found in the `js-jquery`, `js-flot` and `js-dgtable` repos. Copy the associated JavaScript files into a `lib` directory, renaming to take away version numbers and `.min` parts.
To build and test `shake.js` from `html` run:
tsc -p ts # generated shake.js
tslint -p ts # run the linter
Or, for the one liner:
tsc -p ts && tslint -p ts
To test out the `profile.html` just open it after doing the above steps.

View File

@ -0,0 +1,2 @@
var version = "HEAD";
var generated = "10:33pm 30-Mar-2019";

View File

@ -0,0 +1,590 @@
var profile =
[["doesFileExist ../../src/General/GetOpt.hs",0.0001,0,0]
,["../../src/Development/Ninja/All.hs",0.0003,0,0]
,["doesFileExist ../../src/System/IO/Error.hs",0.0001,0,0]
,["doesFileExist ../../src/Data/ByteString.hs",0.0001,0,0]
,["doesFileExist ../../src/Data/Unique.hs",0.0001,0,0]
,["doesFileExist ../../src/System/IO/Unsafe.hs",0.0001,0,0]
,["doesFileExist ../../src/Control/Monad/Trans/Maybe.hs",0.0002,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Progress.hs",0.0001,0,0]
,["doesFileExist ../../src/Data/Binary/Builder.hs",0.0002,0,0]
,["../../src/Development/Shake/Internal/Profile.hs",0.0003,0,0]
,["../../src/Development/Shake/Internal/Core/Types.hs",0.0003,0,0]
,["../../src/Development/Shake/Internal/FilePattern.hs",0.002,0,0]
,["doesFileExist ../../src/Foreign/Ptr.hs",0.0001,0,0]
,["doesFileExist ../../src/General/Ids.hs",0.0002,0,0]
,["doesFileExist ../../src/Paths.hs",0.0001,0,0]
,["doesFileExist ../../src/System/Process.hs",0.0001,0,0]
,["../../src/Development/Shake/Internal/History/Shared.hs",0.0005,0,0]
,["doesFileExist ../../src/Development/Ninja/Env.hs",0.0001,0,0]
,["doesFileExist ../../src/General/Process.hs",0.0001,0,0]
,["../../src/Development/Shake/FilePath.hs",0.0003,0,0]
,["../../src/Development/Shake/Internal/Core/Pool.hs",0.0002,0,0]
,["doesFileExist ../../src/System/FilePath.hs",0.0001,0,0]
,["doesFileExist ../../src/Control/Monad/Trans/Class.hs",0.0002,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Rules/OrderOnly.hs",0.0002,0,0]
,["../../src/General/ListBuilder.hs",0.0003,0,0]
,["../../src/Development/Shake/Internal/Core/Storage.hs",0.0002,0,0]
,["../../src/Development/Shake/Internal/Args.hs",0.0009,0,0]
,["doesFileExist ../../src/GHC/Exts.hs",0.0001,0,0]
,["../../src/Development/Shake/Classes.hs",0.0003,0,0]
,["doesFileExist ../../src/Data/Version.hs",0.0001,0,0]
,["doesFileExist ../../src/System/Exit.hs",0.0001,0,0]
,["../../src/General/Pool.hs",0.0002,0,0]
,["doesFileExist ../../src/System/Console/GetOpt.hs",0.0002,0,0]
,["doesFileExist ../../src/Data/Time.hs",0.0002,0,0]
,["doesFileExist ../../src/General/Cleanup.hs",0.0006,0,0]
,["doesFileExist ../../src/General/Makefile.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Args.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Core/Run.hs",0.0001,0,0]
,["doesFileExist ../../src/General/FileLock.hs",0.0001,0,0]
,["../../src/Development/Ninja/Parse.hs",0.0019,0,0]
,["../../src/Development/Shake/Internal/Core/Rules.hs",0.0011,0,0]
,["doesFileExist ../../src/Foreign/C/String.hs",0.0001,0,0]
,["doesFileExist ../../src/Data/ByteString/Lazy.hs",0.0001,0,0]
,["doesFileExist ../../src/Data/IORef.hs",0.0001,0,0]
,["doesFileExist ../../src/GHC/IO/Exception.hs",0.0001,0,0]
,["doesFileExist ../../src/Data/ByteString/Char8.hs",0.0001,0,0]
,["../../src/General/Fence.hs",0.0002,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Core/Action.hs",0.0002,0,0]
,["doesFileExist ../../src/Data/Hashable.hs",0.0002,0,0]
,["../../src/Development/Shake/Internal/History/Network.hs",0.0003,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Rules/Default.hs",0.0001,0,0]
,["doesFileExist ../../src/System/Info.hs",0.0001,0,0]
,["doesFileExist ../../src/Data/List.hs",0.0001,0,0]
,["../../src/Development/Shake/Internal/Derived.hs",0.0003,0,0]
,["doesFileExist ../../src/Control/Exception.hs",0.0001,0,0]
,["../../src/Development/Shake/Internal/Rules/File.hs",0.0003,0,0]
,["doesFileExist ../../src/Data/IORef/Extra.hs",0.0617,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Core/Build.hs",0.0001,0,0]
,["../../src/General/TypeMap.hs",0.0002,0,0]
,["doesFileExist ../../src/Data/Char.hs",0.0001,0,0]
,["doesFileExist ../../src/System/Posix/Files/ByteString.hs",0.0002,0,0]
,["doesFileExist ../../src/Data/Typeable.hs",0.0001,0,0]
,["doesFileExist ../../src/System/Random.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Shake/Command.hs",0.0002,0,0]
,["../../src/Development/Shake/Internal/History/Bloom.hs",0.0002,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Paths.hs",0.0002,0,0]
,["doesFileExist ../../src/Data/Bits.hs",0.0001,0,0]
,["../../src/Development/Shake/Internal/FileName.hs",0.0003,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/CompactUI.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/History/Shared.hs",0.0001,0,0]
,["../../src/Run.hs",0.0003,0,0]
,["../../src/Development/Shake/Internal/History/Cloud.hs",0.0003,0,0]
,["doesFileExist ../../src/Development/Ninja/Type.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Core/Pool.hs",0.0001,0,0]
,["doesFileExist ../../src/Prelude.hs",0.0001,0,0]
,["../../src/General/Bilist.hs",0.0003,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/FileName.hs",0.0001,0,0]
,["../../src/General/Chunks.hs",0.0003,0,0]
,["doesFileExist ../../src/Data/Primitive/Array.hs",0.0001,0,0]
,["doesFileExist ../../src/Network/HTTP.hs",0.0001,0,0]
,["doesFileExist ../../src/Data/Data.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Demo.hs",0.0001,0,0]
,["../../src/General/Template.hs",0.0003,0,0]
,["doesFileExist ../../src/Development/Ninja/All.hs",0.0002,0,0]
,["../../src/Development/Shake/Internal/History/Types.hs",0.0002,0,0]
,["Development/Shake/Internal/History/Types.dep",0.0017,0,0,[[84],[3]]]
,["Development/Shake/Internal/History/Types.deps",0.0012,0,0,[[85]]]
,["doesFileExist ../../src/Data/HashMap/Strict.hs",0.0001,0,0]
,["doesFileExist ../../src/System/FilePath/Posix.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/FilePattern.hs",0.0001,0,0]
,["doesFileExist ../../src/Network/URI.hs",0.0001,0,0]
,["../../src/General/FileLock.hs",0.0002,0,0]
,["../../src/Development/Shake/Internal/Rules/Directory.hs",0.0003,0,0]
,["doesFileExist ../../src/Development/Ninja/Lexer.hs",0.0001,0,0]
,["doesFileExist ../../src/Control/Monad/Fix.hs",0.0001,0,0]
,["doesFileExist ../../src/General/Fence.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/History/Cloud.hs",0.0001,0,0]
,["doesFileExist ../../src/System/Environment.hs",0.0001,0,0]
,["doesFileExist ../../src/Data/Heap.hs",0.0001,0,0]
,["doesFileExist ../../src/Data/HashSet.hs",0.0001,0,0]
,["doesFileExist ../../src/Control/Monad/IO/Class.hs",0.0002,0,0]
,["../../src/Development/Shake/Internal/Rules/Rerun.hs",0.0003,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Core/Rules.hs",0.0001,0,0]
,["doesFileExist ../../src/Control/Monad/Trans/Reader.hs",0.0001,0,0]
,["doesFileExist ../../src/Control/Monad/ST.hs",0.0001,0,0]
,["doesFileExist ../../src/Data/Binary/Put.hs",0.0002,0,0]
,["doesFileExist ../../src/System/Posix/IO.hs",0.0001,0,0]
,["doesFileExist ../../src/System/IO.hs",0.0001,0,0]
,["../../src/Development/Shake/Internal/Resource.hs",0.0003,0,0]
,["doesFileExist ../../src/Unsafe/Coerce.hs",0.0009,0,0]
,["../../src/Development/Shake/Internal/Rules/Files.hs",0.0003,0,0]
,["doesFileExist ../../src/General/Bilist.hs",0.0001,0,0]
,["../../src/General/EscCodes.hs",0.0003,0,0]
,["../../src/Development/Shake/Internal/CompactUI.hs",0.0004,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/History/Types.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Shake.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/History/Network.hs",0.0001,0,0]
,["doesFileExist ../../src/Data/List/Extra.hs",0.0001,0,0]
,["../../src/General/Process.hs",0.0002,0,0]
,["doesFileExist ../../src/System/IO/Extra.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/FileInfo.hs",0.0007,0,0]
,["../../src/Development/Shake/Internal/History/Symlink.hs",0.0004,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Rules/Directory.hs",0.0001,0,0]
,["../../src/Development/Shake/Internal/Rules/Oracle.hs",0.0006,0,0]
,["../../src/Development/Shake/Internal/Rules/Default.hs",0.0004,0,0]
,["../../src/Development/Shake/Internal/Progress.hs",0.0003,0,0]
,["doesFileExist ../../src/Data/ByteString/Lazy/Char8.hs",0.0002,0,0]
,["doesFileExist ../../src/Data/Dynamic.hs",0.0002,0,0]
,["doesFileExist ../../src/Data/ByteString/UTF8.hs",0.0001,0,0]
,["doesFileExist ../../src/Data/Monoid.hs",0.0004,0,0]
,["doesFileExist ../../src/Language/Javascript/Flot.hs",0.0002,0,0]
,["doesFileExist ../../src/General/Wait.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Shake/FilePath.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/History/Server.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Ninja/Parse.hs",0.0001,0,0]
,["doesFileExist ../../src/System/FilePattern/Directory.hs",0.0001,0,0]
,["doesFileExist ../../src/Data/Tuple/Extra.hs",0.0001,0,0]
,["../../src/Development/Ninja/Type.hs",0.0005,0,0]
,["doesFileExist ../../src/Numeric/Extra.hs",0.0007,0,0]
,["doesFileExist ../../src/GHC/Conc.hs",0.0009,0,0]
,["doesFileExist ../../src/Data/Binary/Get.hs",0.0001,0,0]
,["../../src/Development/Shake/Internal/Core/Run.hs",0.0003,0,0]
,["doesFileExist ../../src/General/Template.hs",0.0001,0,0]
,["OracleQ (GhcPkg ())",0.1414,0,0,[],[["ghc-pkg",0.4508,0.5896]]]
,["doesFileExist ../../src/Language/Javascript/JQuery.hs",0.004,0,0]
,["../../src/Development/Shake/Internal/Demo.hs",0.0003,0,0]
,["doesFileExist ../../src/General/TypeMap.hs",0.0001,0,0]
,["doesFileExist ../../src/General/Timing.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/History/Bloom.hs",0.0001,0,0]
,["../../src/Development/Shake.hs",0.0003,0,0]
,["doesFileExist ../../src/Control/Concurrent.hs",0.0001,0,0]
,["doesFileExist ../../src/System/Time/Extra.hs",0.0001,0,0]
,["../../src/Development/Shake/Internal/CmdOption.hs",0.0005,0,0]
,["Development/Shake/Internal/CmdOption.dep",0.0145,0,0,[[152],[80],[126]]]
,["Development/Shake/Internal/CmdOption.deps",0.0013,0,0,[[153]]]
,["doesFileExist ../../src/Development/Shake/Internal/Resource.hs",0.0007,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Rules/Files.hs",0.0001,0,0]
,["doesFileExist ../../src/General/ListBuilder.hs",0.0001,0,0]
,["../../src/Development/Shake/Internal/Errors.hs",0.0003,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Core/Storage.hs",0.0001,0,0]
,["doesFileExist ../../src/Foreign.hs",0.0001,0,0]
,["../../src/General/Makefile.hs",0.0003,0,0]
,["General/Makefile.dep",0.0026,0,0,[[161],[45],[59]]]
,["General/Makefile.deps",0.0018,0,0,[[162]]]
,["../../src/General/Cleanup.hs",0.0006,0,0]
,["doesFileExist ../../src/Foreign/Marshal/Alloc.hs",0.0001,0,0]
,["../../src/General/Thread.hs",0.0002,0,0]
,["doesFileExist ../../src/General/Pool.hs",0.0001,0,0]
,["doesFileExist ../../src/Control/Monad/Extra.hs",0.0001,0,0]
,["../../src/Development/Shake/Internal/Core/Build.hs",0.0002,0,0]
,["doesFileExist ../../src/Data/Either.hs",0.0001,0,0]
,["doesFileExist ../../src/Foreign/C/Error.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Value.hs",0.0001,0,0]
,["../../src/Development/Shake/Internal/Core/Monad.hs",0.0005,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Errors.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Rules/Oracle.hs",0.0002,0,0]
,["../../src/Development/Shake/Internal/Rules/OrderOnly.hs",0.0003,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Profile.hs",0.0002,0,0]
,["../../src/Development/Shake/Internal/Options.hs",0.0003,0,0]
,["doesFileExist ../../src/Data/Function.hs",0.0001,0,0]
,["doesFileExist ../../src/General/EscCodes.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Shake/Database.hs",0.0001,0,0]
,["doesFileExist ../../src/General/Intern.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Core/Monad.hs",0.0001,0,0]
,["doesFileExist ../../src/Control/Exception/Extra.hs",0.0001,0,0]
,["General/Template.dep",0.0041,0,0,[[82],[88],[184],[59],[5],[126],[130],[144]]]
,["General/Template.deps",0.0011,0,0,[[185]]]
,["doesFileExist ../../src/Control/DeepSeq.hs",0.0002,0,0]
,["doesFileExist ../../src/Control/Monad.hs",0.0001,0,0]
,["Development/Ninja/Parse.dep",0.0092,0,0,[[39],[45],[17],[72],[93],[188]]]
,["doesFileExist ../../src/Development/Shake/Internal/Derived.hs",0.0001,0,0]
,["../../shake.cabal",0.0002,0,0]
,[".pkgs",0.0044,0,0,[[191]]]
,["OracleQ (GhcFlags ())",0.0005,0,0,[[192]]]
,["Development/Shake/Internal/History/Types.o Development/Shake/Internal/History/Types.hi",0.532,0,0,[[86],[84],[143],[193]],[["ghc",3.3763,3.903]]]
,["Development/Shake/Internal/History/Types.hi",0.0004,0,0,[[194]]]
,["Development/Shake/Internal/History/Types.o",0.0006,0,0,[[194]]]
,["Development/Shake/Internal/CmdOption.o Development/Shake/Internal/CmdOption.hi",0.7516,0,0,[[154],[152],[143],[193]],[["ghc",1.8268,2.5737]]]
,["Development/Shake/Internal/CmdOption.o",0.0003,0,0,[[197]]]
,["Development/Shake/Internal/CmdOption.hi",0.0003,0,0,[[197]]]
,["General/Makefile.o General/Makefile.hi",0.5911,0,0,[[163],[161],[143],[193]],[["ghc",1.0346,1.6191]]]
,["General/Makefile.hi",0.0003,0,0,[[200]]]
,["General/Makefile.o",0.0003,0,0,[[200]]]
,["General/Template.o General/Template.hi",0.6362,0,0,[[186],[82],[143],[193]],[["ghc",2.8643,3.4941]]]
,["General/Template.o",0.0003,0,0,[[203]]]
,["General/Template.hi",0.0006,0,0,[[203]]]
,["doesFileExist ../../src/GHC/Stack.hs",0.0002,0,0]
,["doesFileExist ../../src/Control/Applicative.hs",0.0001,0,0]
,["../../src/Development/Shake/Command.hs",0.0002,0,0]
,["../../src/Development/Ninja/Lexer.hs",0.0005,0,0]
,["doesFileExist ../../src/General/Binary.hs",0.0001,0,0]
,["doesFileExist ../../src/General/Thread.hs",0.0001,0,0]
,["doesFileExist ../../src/Data/Functor.hs",0.0001,0,0]
,["General/TypeMap.dep",0.0029,0,0,[[58],[87],[61],[109],[212],[74]]]
,["General/TypeMap.deps",0.0012,0,0,[[213]]]
,["General/TypeMap.o General/TypeMap.hi",0.5423,0,0,[[214],[58],[143],[193]],[["ghc",0.6005,1.1343]]]
,["General/TypeMap.o",0.0014,0,0,[[215]]]
,["General/TypeMap.hi",0.0003,0,0,[[215]]]
,["doesFileExist ../../src/Control/Monad/Fail.hs",0.0001,0,0]
,["doesFileExist ../../src/Data/Maybe.hs",0.0001,0,0]
,["Development/Shake/Internal/History/Network.dep",0.0024,0,0,[[49],[79],[90],[52],[219],[42]]]
,["Development/Shake/Internal/History/Network.deps",0.0012,0,0,[[220]]]
,["Development/Shake/Internal/History/Network.o Development/Shake/Internal/History/Network.hi",0.7966,0,0,[[221],[49],[143],[193]],[["ghc",3.5012,4.2912]]]
,["Development/Shake/Internal/History/Network.hi",0.0014,0,0,[[222]]]
,["Development/Shake/Internal/History/Network.o",0.0007,0,0,[[222]]]
,["Development/Ninja/Type.dep",0.0152,0,0,[[137],[17],[45],[219]]]
,["General/Cleanup.dep",0.0052,0,0,[[164],[54],[87],[43],[117],[219]]]
,["General/Cleanup.deps",0.0017,0,0,[[226]]]
,["General/Cleanup.o General/Cleanup.hi",0.6072,0,0,[[227],[164],[143],[193]],[["ghc",2.258,2.8553]]]
,["General/Cleanup.hi",0.0004,0,0,[[228]]]
,["General/Cleanup.o",0.0003,0,0,[[228]]]
,["../../src/General/Wait.hs",0.0002,0,0]
,["../../src/General/GetOpt.hs",0.0003,0,0]
,["General/GetOpt.dep",0.0039,0,0,[[232],[32],[99],[219],[170],[117]]]
,["General/GetOpt.deps",0.0015,0,0,[[233]]]
,["General/GetOpt.o General/GetOpt.hi",0.6806,0,0,[[234],[232],[143],[193]],[["ghc",4.5104,5.1844]]]
,["General/GetOpt.o",0.0005,0,0,[[235]]]
,["General/GetOpt.hi",0.0003,0,0,[[235]]]
,["../../src/Paths.hs",0.0002,0,0]
,["doesFileExist ../../src/Development/Shake/Classes.hs",0.0002,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Options.hs",0.0002,0,0]
,["../../src/General/Intern.hs",0.0002,0,0]
,["doesFileExist ../../src/Foreign/Storable.hs",0.0002,0,0]
,["../../src/Development/Shake/Internal/History/Server.hs",0.0002,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Rules/Rerun.hs",0.0002,0,0]
,["../../src/Development/Shake/Internal/History/Serialise.hs",0.0004,0,0]
,["../../src/Development/Shake/Internal/FileInfo.hs",0.0003,0,0]
,["doesFileExist ../../src/Data/Binary.hs",0.0001,0,0]
,["Development/Shake/Classes.dep",0.0028,0,0,[[28],[48],[61],[247],[187]]]
,["Development/Shake/Classes.deps",0.0013,0,0,[[248]]]
,["Development/Shake/Classes.o Development/Shake/Classes.hi",0.4995,0,0,[[249],[28],[143],[193]],[["ghc",0.6007,1.0927]]]
,["Development/Shake/Classes.hi",0.0008,0,0,[[250]]]
,["Development/Shake/Classes.o",0.0005,0,0,[[250]]]
,["../../src/Development/Ninja/Env.hs",0.0004,0,0]
,["Development/Ninja/Env.dep",0.0041,0,0,[[253],[87],[48],[43]]]
,["Development/Ninja/Env.deps",0.0014,0,0,[[254]]]
,["Development/Ninja/Env.o Development/Ninja/Env.hi",0.6363,0,0,[[255],[253],[143],[193]],[["ghc",1.625,2.2508]]]
,["Development/Ninja/Env.o",0.0005,0,0,[[256]]]
,["Development/Ninja/Env.hi",0.0003,0,0,[[256]]]
,["Development/Ninja/Type.deps",0.0027,0,0,[[225],[255]]]
,["Development/Ninja/Type.o Development/Ninja/Type.hi",0.6863,0,0,[[259],[137,258],[143],[193]],[["ghc",4.2972,4.9755]]]
,["Development/Ninja/Type.hi",0.0003,0,0,[[260]]]
,["Development/Ninja/Type.o",0.0003,0,0,[[260]]]
,["../../src/Development/Shake/Internal/Core/Action.hs",0.0004,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/CmdOption.hs",0.0002,0,0]
,["../../src/General/Ids.hs",0.0003,0,0]
,["doesFileExist ../../src/GHC/IO.hs",0.0001,0,0]
,["General/Ids.dep",0.0079,0,0,[[265],[56],[78],[54],[182],[168],[117],[219],[212],[87],[74],[266],[27]]]
,["doesFileExist ../../src/System/Directory.hs",0.0001,0,0]
,["../../src/General/Timing.hs",0.0002,0,0]
,["doesFileExist ../../src/Data/Either/Extra.hs",0.0001,0,0]
,["General/Fence.dep",0.0023,0,0,[[46],[188],[100],[219],[270],[43]]]
,["General/Fence.deps",0.001,0,0,[[271]]]
,["General/Fence.o General/Fence.hi",0.6501,0,0,[[272],[46],[143],[193]],[["ghc",1.1762,1.8127]]]
,["General/Fence.hi",0.0004,0,0,[[273]]]
,["General/Fence.o",0.0008,0,0,[[273]]]
,["doesFileExist ../../src/System/Info/Extra.hs",0.0002,0,0]
,["Development/Shake/FilePath.dep",0.0042,0,0,[[19],[276],[21],[88]]]
,["Development/Shake/FilePath.deps",0.0014,0,0,[[277]]]
,["Development/Shake/FilePath.o Development/Shake/FilePath.hi",0.576,0,0,[[278],[19],[143],[193]],[["ghc",0.6008,1.1707]]]
,["Development/Shake/FilePath.o",0.0003,0,0,[[279]]]
,["Development/Shake/FilePath.hi",0.0003,0,0,[[279]]]
,["Development/Shake/Internal/FilePattern.dep",0.0145,0,0,[[11],[174],[21],[117],[188],[59],[219],[276]]]
,["Development/Shake/Internal/FileName.dep",0.0097,0,0,[[67],[45],[128],[239],[21],[210],[276],[52]]]
,["doesFileExist ../../src/Development/Shake/Internal/History/Symlink.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Rules/File.hs",0.0001,0,0]
,["Development/Shake/Internal/Rules/Default.dep",0.0071,0,0,[[124],[102],[122],[285],[156],[244]]]
,["doesFileExist ../../src/System/Posix/Files.hs",0.0001,0,0]
,["doesFileExist ../../src/Data/ByteString/Lazy/Internal.hs",0.0033,0,0]
,["../../src/Development/Shake/Internal/Value.hs",0.0003,0,0]
,["Development/Shake/Internal/Value.dep",0.0088,0,0,[[289],[239],[174],[61],[66],[109]]]
,["doesFileExist ../../src/Data/ByteString/Unsafe.hs",0.0001,0,0]
,["doesFileExist ../../src/System/FilePattern.hs",0.0001,0,0]
,["doesFileExist ../../src/System/Directory/Extra.hs",0.0001,0,0]
,["Development/Shake/Internal/Args.dep",0.03,0,0,[[26],[65],[240],[102],[174],[68],[81],[47],[132],[285],[7],[181],[147],[211],[0],[180],[136],[184],[188],[170],[52],[219],[293],[97],[30],[151]]]
,["doesFileExist ../../src/General/Extra.hs",0.0001,0,0]
,["Development/Shake/Internal/History/Symlink.dep",0.0046,0,0,[[121],[168],[295],[268],[21],[12],[41],[287]]]
,["Development/Shake/Internal/Errors.dep",0.006,0,0,[[158],[136],[184],[100],[295],[61],[117],[219]]]
,["Development/Shake/Internal/CompactUI.dep",0.0071,0,0,[[113],[264],[240],[7],[151],[295],[54],[211],[180],[43],[168]]]
,["Run.dep",0.0066,0,0,[[70],[83],[97],[115],[132],[147],[168],[184],[219],[268],[295],[0],[15],[30]]]
,["Development/Shake/Internal/Demo.dep",0.0662,0,0,[[145],[65],[63],[184],[188],[59],[52],[219],[268],[30],[21],[295],[132],[107],[276]]]
,["General/Timing.dep",0.0088,0,0,[[269],[43],[5],[136],[138],[295],[151]]]
,["Development/Ninja/All.dep",0.014,0,0,[[1],[17],[72],[134],[115],[239],[3],[45],[268],[87],[99],[136],[184],[188],[219],[59],[117],[276],[295],[147],[35],[76],[120],[174],[285],[23]]]
,["General/Process.dep",0.0099,0,0,[[118],[150],[187],[184],[168],[117],[219],[171],[30],[119],[276],[15],[151],[4],[43],[45],[42],[295],[174],[44]]]
,["../../src/General/Extra.hs",0.0003,0,0]
,["doesFileExist ../../src/Data/Version/Extra.hs",0.0001,0,0]
,["Paths_shake.dep",0.0013,0,0,[[238],[305]]]
,["Paths_shake.deps",0.001,0,0,[[306]]]
,["Paths_shake.o Paths_shake.hi",0.4356,0,0,[[307],[238],[143],[193]],[["ghc",0.6004,1.0302]]]
,["Paths_shake.o",0.0014,0,0,[[308]]]
,["Paths_shake.hi",0.0003,0,0,[[308]]]
,["doesFileExist ../../src/Numeric.hs",0.0001,0,0]
,["doesFileExist ../../src/Development/Shake/Internal/Core/Types.hs",0.0001,0,0]
,["Development/Shake/Internal/Rules/Rerun.dep",0.0032,0,0,[[101],[102],[312],[57],[47],[239],[3],[210]]]
,["Development/Shake/Internal/Rules/Oracle.dep",0.0121,0,0,[[123],[312],[102],[240],[57],[172],[239],[3],[42],[188],[247],[210],[295]]]
,["Development/Shake/Internal/Core/Pool.dep",0.0057,0,0,[[20],[54],[167],[312],[183],[151],[270],[100],[95]]]
,["Development/Shake/Internal/Rules/OrderOnly.dep",0.0052,0,0,[[176],[312],[47],[285],[45]]]
,["Development/Shake/Internal/Rules/Files.dep",0.0132,0,0,[[110],[188],[100],[219],[117],[61],[210],[47],[312],[57],[102],[174],[295],[76],[239],[244],[285],[89],[132],[120],[240],[129],[74]]]
,["Development/Shake/Internal/Core/Build.dep",0.0239,0,0,[[169],[239],[167],[172],[174],[312],[47],[69],[96],[240],[183],[131],[45],[100],[295],[182],[54],[168],[138],[87],[13],[102],[61],[56],[219],[117],[270],[151]]]
,["Development/Shake.dep",0.0184,0,0,[[149],[74],[100],[172],[240],[312],[47],[102],[155],[190],[174],[7],[36],[63],[89],[122],[285],[156],[175],[23],[244]]]
,["Development/Shake/Internal/Rules/Directory.dep",0.0104,0,0,[[92],[168],[100],[219],[247],[52],[136],[99],[268],[97],[312],[47],[102],[57],[172],[239],[132],[89],[295],[210]]]
,["Development/Shake/Internal/Progress.dep",0.0183,0,0,[[125],[207],[136],[184],[168],[268],[15],[21],[59],[43],[52],[219],[240],[312],[45],[126],[138],[142],[180],[295],[65],[151],[13],[41]]]
,["Development/Shake/Internal/Derived.dep",0.0175,0,0,[[53],[168],[100],[268],[21],[107],[119],[174],[155],[312],[47],[102],[240],[285],[3],[87],[295],[117],[48],[61],[127]]]
,["Development/Shake/Internal/Profile.dep",0.0085,0,0,[[9],[142],[136],[179],[117],[219],[21],[119],[138],[295],[174],[312],[172],[13],[99],[65],[239],[151],[87],[126],[45],[182]]]
,["doesFileExist ../../src/General/Chunks.hs",0.0001,0,0]
,["Development/Shake/Internal/History/Shared.dep",0.0076,0,0,[[16],[172],[114],[284],[239],[210],[295],[324],[168],[293],[21],[107],[311],[120],[131],[76],[129],[100],[219],[3],[74]]]
,["doesFileExist ../../src/Control/Concurrent/Extra.hs",0.0001,0,0]
,["General/Pool.dep",0.0089,0,0,[[31],[326],[151],[54],[168],[147],[211],[98],[99],[56],[62]]]
,["Development/Shake/Internal/Core/Run.dep",0.0127,0,0,[[141],[54],[136],[326],[100],[210],[239],[159],[69],[96],[13],[182],[146],[131],[168],[61],[138],[117],[87],[127],[219],[43],[268],[151],[3],[312],[47],[102],[167],[7],[172],[177],[240],[174],[147],[211],[295],[34],[129],[74]]]
,["General/Thread.dep",0.0067,0,0,[[166],[34],[48],[326],[54],[295],[168]]]
,["Development/Shake/Internal/History/Cloud.dep",0.0104,0,0,[[71],[172],[114],[116],[133],[148],[326],[151],[188],[100],[6],[22],[95],[87],[61],[270],[210],[295],[131]]]
,["Development/Shake/Internal/Resource.dep",0.0092,0,0,[[108],[179],[5],[326],[95],[184],[136],[43],[168],[111],[167],[47],[312],[183],[73],[100],[151]]]
,["General/Wait.dep",0.004,0,0,[[231],[168],[100],[326],[56],[117],[78],[27],[218]]]
,["General/Wait.deps",0.001,0,0,[[332]]]
,["General/Wait.o General/Wait.hi",1.0318,0,0,[[333],[231],[143],[193]],[["ghc",1.0995,2.123]]]
,["General/Wait.hi",0.0003,0,0,[[334]]]
,["General/Wait.o",0.0014,0,0,[[334]]]
,["Development/Shake/Internal/Core/Action.dep",0.0147,0,0,[[263],[54],[168],[100],[187],[61],[268],[292],[135],[326],[219],[136],[43],[117],[138],[295],[87],[13],[182],[239],[183],[69],[167],[312],[102],[73],[172],[120],[76],[240],[174],[34],[95]]]
,["General/Extra.dep",0.0188,0,0,[[304],[184],[59],[117],[97],[132],[187],[311],[34],[61],[119],[151],[5],[276],[62],[268],[30],[138],[242],[326],[219],[48],[78],[188],[104],[139],[206]]]
,["General/Extra.deps",0.0041,0,0,[[338],[278,227]]]
,["General/Extra.o General/Extra.hi",1.364,0,0,[[339],[304,281,229],[143],[193]],[["ghc",3.4583,4.8013]]]
,["General/Extra.hi",0.001,0,0,[[340]]]
,["General/Extra.o",0.0003,0,0,[[340]]]
,["Development/Shake/Internal/History/Symlink.deps",0.0029,0,0,[[296],[339]]]
,["Development/Shake/Internal/History/Symlink.o Development/Shake/Internal/History/Symlink.hi",1.1794,0,0,[[343],[121,281,229,341],[143],[193]],[["ghc",4.8226,5.9703]]]
,["Development/Shake/Internal/History/Symlink.hi",0.0009,0,0,[[344]]]
,["Development/Shake/Internal/History/Symlink.o",0.0004,0,0,[[344]]]
,["Development/Shake/Internal/Errors.deps",0.0063,0,0,[[297],[339]]]
,["Development/Shake/Internal/Errors.o Development/Shake/Internal/Errors.hi",1.0817,0,0,[[347],[158,281,229,341],[143],[193]],[["ghc",4.9817,6.0552]]]
,["Development/Shake/Internal/Errors.o",0.0003,0,0,[[348]]]
,["Development/Shake/Internal/Errors.hi",0.0003,0,0,[[348]]]
,["Development/Shake/Internal/FilePattern.deps",0.0084,0,0,[[282],[347]]]
,["Development/Shake/Internal/FilePattern.o Development/Shake/Internal/FilePattern.hi",0.844,0,0,[[351],[11,281,350,229,341],[143],[193]],[["ghc",6.7192,7.5541]]]
,["Development/Shake/Internal/FilePattern.o",0.0006,0,0,[[352]]]
,["Development/Shake/Internal/FilePattern.hi",0.0006,0,0,[[352]]]
,["Development/Shake/Internal/Value.deps",0.0033,0,0,[[290],[249,347]]]
,["Development/Shake/Internal/Value.o Development/Shake/Internal/Value.hi",0.8159,0,0,[[355],[289,251,281,350,229,341],[143],[193]],[["ghc",6.3347,7.1393]]]
,["Development/Shake/Internal/Value.hi",0.0006,0,0,[[356]]]
,["Development/Shake/Internal/Value.o",0.0003,0,0,[[356]]]
,["General/Process.deps",0.0155,0,0,[[303],[339,347]]]
,["General/Process.o General/Process.hi",0.9122,0,0,[[359],[118,281,350,229,341],[143],[193]],[["ghc",6.2048,7.1061]]]
,["General/Process.o",0.0003,0,0,[[360]]]
,["General/Process.hi",0.0005,0,0,[[360]]]
,["General/Timing.deps",0.007,0,0,[[301],[339]]]
,["General/Timing.o General/Timing.hi",0.6649,0,0,[[363],[269,281,229,341],[143],[193]],[["ghc",4.8699,5.5256]]]
,["General/Timing.o",0.0003,0,0,[[364]]]
,["General/Timing.hi",0.0005,0,0,[[364]]]
,["General/Thread.deps",0.0034,0,0,[[329],[227,339]]]
,["General/Thread.o General/Thread.hi",0.8005,0,0,[[367],[166,281,229,341],[143],[193]],[["ghc",5.5352,6.3282]]]
,["General/Thread.hi",0.0003,0,0,[[368]]]
,["General/Thread.o",0.0003,0,0,[[368]]]
,["General/Pool.deps",0.0052,0,0,[[327],[363,367]]]
,["General/Pool.o General/Pool.hi",0.8336,0,0,[[371],[31,281,229,341,369,366],[143],[193]],[["ghc",7.1157,7.9387]]]
,["General/Pool.o",0.0008,0,0,[[372]]]
,["General/Pool.hi",0.0004,0,0,[[372]]]
,["doesFileExist ../../src/Development/Shake/Internal/History/Serialise.hs",0.0002,0,0]
,["Development/Shake/Internal/History/Server.dep",0.006,0,0,[[243],[148],[375],[172],[210],[295],[87],[42],[3],[120],[114],[116],[61]]]
,["../../src/Development/Shake/Database.hs",0.0003,0,0]
,["Development/Shake/Database.dep",0.0127,0,0,[[377],[326],[54],[188],[100],[43],[34],[174],[240],[102],[37],[312],[50]]]
,["doesFileExist ../../src/Data/Word.hs",0.0002,0,0]
,["General/EscCodes.dep",0.0068,0,0,[[112],[59],[107],[97],[5],[379],[66],[12],[242],[165]]]
,["General/EscCodes.deps",0.0012,0,0,[[380]]]
,["General/EscCodes.o General/EscCodes.hi",0.88,0,0,[[381],[112],[143],[193]],[["ghc",2.5782,3.4493]]]
,["General/EscCodes.o",0.0006,0,0,[[382]]]
,["General/EscCodes.hi",0.0003,0,0,[[382]]]
,["General/Intern.dep",0.0025,0,0,[[241],[239],[242],[379],[74],[87],[52]]]
,["General/Intern.deps",0.0021,0,0,[[385],[249]]]
,["General/Intern.o General/Intern.hi",0.7673,0,0,[[386],[241,251],[143],[193]],[["ghc",2.132,2.8908]]]
,["General/Intern.o",0.0003,0,0,[[387]]]
,["General/Intern.hi",0.0005,0,0,[[387]]]
,["General/Ids.deps",0.0076,0,0,[[267],[386]]]
,["General/Ids.o General/Ids.hi",0.8581,0,0,[[390],[265,251,389],[143],[193]],[["ghc",2.8992,3.7487]]]
,["General/Ids.o",0.001,0,0,[[391]]]
,["General/Ids.hi",0.0003,0,0,[[391]]]
,["Development/Shake/Internal/Rules/File.dep",0.0145,0,0,[[55],[168],[100],[61],[52],[219],[45],[99],[242],[379],[129],[210],[295],[312],[102],[57],[47],[76],[244],[239],[132],[89],[120],[240],[174],[21],[5],[74]]]
,["Development/Shake/Internal/FileInfo.dep",0.0102,0,0,[[246],[48],[184],[239],[76],[288],[59],[379],[311],[107],[160],[2],[268],[33],[174],[188],[45],[41],[44],[60]]]
,["General/FileLock.dep",0.0049,0,0,[[91],[184],[21],[295],[34],[188],[66],[379],[12],[41],[107],[106]]]
,["General/FileLock.deps",0.0024,0,0,[[396],[339,227]]]
,["General/FileLock.o General/FileLock.hi",0.7159,0,0,[[397],[91,281,229,341],[143],[193]],[["ghc",6.0052,6.7105]]]
,["General/FileLock.o",0.0003,0,0,[[398]]]
,["General/FileLock.hi",0.0003,0,0,[[398]]]
,["Development/Shake/Internal/Core/Storage.dep",0.0086,0,0,[[25],[324],[34],[210],[182],[240],[174],[147],[38],[13],[184],[168],[129],[270],[33],[59],[379],[51],[239],[311],[295],[117],[219],[21],[128],[87],[45],[3],[74]]]
,["General/Chunks.dep",0.0063,0,0,[[77],[151],[21],[326],[168],[54],[107],[268],[3],[379],[129],[210],[295],[34],[211],[74]]]
,["doesFileExist ../../src/Data/ByteString/Internal.hs",0.0002,0,0]
,["Development/Ninja/Lexer.dep",0.0116,0,0,[[209],[136],[59],[45],[291],[72],[403],[5],[379],[12],[242],[27]]]
,["Development/Ninja/Lexer.deps",0.006,0,0,[[404],[259]]]
,["Development/Ninja/Lexer.o Development/Ninja/Lexer.hi",1.0702,0,0,[[405],[209,258,261],[143],[193]],[["ghc",7.7163,8.7791]]]
,["Development/Ninja/Lexer.o",0.0003,0,0,[[406]]]
,["Development/Ninja/Lexer.hi",0.0003,0,0,[[406]]]
,["Development/Ninja/Parse.deps",0.0057,0,0,[[189],[255,259,405]]]
,["Development/Ninja/Parse.o Development/Ninja/Parse.hi",0.6308,0,0,[[409],[39,258,408,261],[143],[193]],[["ghc",8.7861,9.4093]]]
,["Development/Ninja/Parse.hi",0.0004,0,0,[[410]]]
,["Development/Ninja/Parse.o",0.0003,0,0,[[410]]]
,["doesFileExist ../../src/Data/Semigroup.hs",0.0003,0,0]
,["General/ListBuilder.dep",0.0018,0,0,[[24],[413]]]
,["General/ListBuilder.deps",0.001,0,0,[[414]]]
,["General/ListBuilder.o General/ListBuilder.hi",0.5663,0,0,[[415],[24],[143],[193]],[["ghc",7.1502,7.7115]]]
,["General/ListBuilder.o",0.0003,0,0,[[416]]]
,["General/ListBuilder.hi",0.0004,0,0,[[416]]]
,["General/Bilist.dep",0.0018,0,0,[[75],[413]]]
,["General/Bilist.deps",0.0012,0,0,[[419]]]
,["General/Bilist.o General/Bilist.hi",0.6522,0,0,[[420],[75],[143],[193]],[["ghc",2.7239,3.3698]]]
,["General/Bilist.hi",0.0003,0,0,[[421]]]
,["General/Bilist.o",0.0011,0,0,[[421]]]
,["Development/Shake/Internal/Core/Monad.dep",0.0154,0,0,[[173],[184],[100],[43],[413],[74],[218]]]
,["Development/Shake/Internal/Core/Monad.deps",0.0013,0,0,[[424]]]
,["Development/Shake/Internal/Core/Monad.o Development/Shake/Internal/Core/Monad.hi",0.9616,0,0,[[425],[173],[143],[193]],[["ghc",3.909,4.8636]]]
,["Development/Shake/Internal/Core/Monad.o",0.0006,0,0,[[426]]]
,["Development/Shake/Internal/Core/Monad.hi",0.0004,0,0,[[426]]]
,["Development/Shake/Command.dep",0.0187,0,0,[[208],[136],[168],[100],[59],[270],[117],[219],[413],[268],[97],[30],[119],[15],[276],[151],[5],[3],[126],[295],[18],[264],[47],[312],[132],[89],[240],[285],[190]]]
,["Development/Shake/Internal/History/Serialise.dep",0.0064,0,0,[[245],[148],[295],[210],[13],[117],[172],[120],[114],[87],[413],[61],[74]]]
,["Development/Shake/Internal/Core/Rules.dep",0.0166,0,0,[[40],[207],[136],[54],[168],[94],[100],[103],[239],[210],[295],[61],[80],[117],[87],[146],[219],[43],[413],[42],[8],[105],[140],[157],[218],[312],[183],[172],[240],[174]]]
,["Development/Shake/Internal/Options.dep",0.0238,0,0,[[178],[80],[117],[136],[219],[127],[188],[295],[87],[89],[45],[128],[264],[413],[74]]]
,["Development/Shake/Internal/Options.deps",0.0096,0,0,[[432],[339,351,154]]]
,["Development/Shake/Internal/Options.o Development/Shake/Internal/Options.hi",1.5102,0,0,[[433],[178,281,199,350,354,229,341],[143],[193]],[["ghc",7.5631,9.0593]]]
,["Development/Shake/Internal/Options.hi",0.0004,0,0,[[434]]]
,["Development/Shake/Internal/Options.o",0.0005,0,0,[[434]]]
,["Development/Shake/Internal/Core/Types.dep",0.0089,0,0,[[10],[100],[187],[242],[379],[61],[210],[219],[52],[54],[295],[326],[69],[96],[114],[131],[174],[146],[43],[45],[138],[151],[182],[99],[87],[13],[136],[167],[183],[172],[240],[239],[413],[34],[74],[218]]]
,["Development/Shake/Internal/History/Bloom.dep",0.0027,0,0,[[64],[379],[66],[48],[413],[242],[12],[74]]]
,["Development/Shake/Internal/History/Bloom.deps",0.0015,0,0,[[438]]]
,["Development/Shake/Internal/History/Bloom.o Development/Shake/Internal/History/Bloom.hi",0.6861,0,0,[[439],[64],[143],[193]],[["ghc",1.1417,1.8181]]]
,["Development/Shake/Internal/History/Bloom.o",0.0004,0,0,[[440]]]
,["Development/Shake/Internal/History/Bloom.hi",0.0004,0,0,[[440]]]
,["../../src/Development/Shake/Internal/Paths.hs",0.0002,0,0]
,["Development/Shake/Internal/Paths.dep",0.0066,0,0,[[443],[14],[54],[168],[29],[268],[21],[276],[5],[97],[295],[42]]]
,["Development/Shake/Internal/Paths.deps",0.0121,0,0,[[444],[307,339]]]
,["Development/Shake/Internal/Paths.o Development/Shake/Internal/Paths.hi",1.0141,0,0,[[445],[443,281,229,341,310],[143],[193]],[["ghc",5.1914,6.1978]]]
,["Development/Shake/Internal/Paths.hi",0.0004,0,0,[[446]]]
,["Development/Shake/Internal/Paths.o",0.0003,0,0,[[446]]]
,["../../src/General/Binary.hs",0.0003,0,0]
,["General/Binary.dep",0.0082,0,0,[[449],[239],[188],[247],[117],[136],[242],[12],[5],[3],[403],[291],[42],[128],[413]]]
,["General/Binary.deps",0.0022,0,0,[[450],[249]]]
,["General/Binary.o General/Binary.hi",0.897,0,0,[[451],[449,251],[143],[193]],[["ghc",1.8267,2.7129]]]
,["General/Binary.hi",0.0003,0,0,[[452]]]
,["General/Binary.o",0.0003,0,0,[[452]]]
,["Development/Shake/Internal/FileName.deps",0.0072,0,0,[[283],[249,451]]]
,["Development/Shake/Internal/FileName.o Development/Shake/Internal/FileName.hi",0.7527,0,0,[[455],[67,251,453],[143],[193]],[["ghc",3.7574,4.5026]]]
,["Development/Shake/Internal/FileName.hi",0.0006,0,0,[[456]]]
,["Development/Shake/Internal/FileName.o",0.001,0,0,[[456]]]
,["Development/Shake/Internal/FileInfo.deps",0.0056,0,0,[[395],[249,455,347]]]
,["Development/Shake/Internal/FileInfo.o Development/Shake/Internal/FileInfo.hi",0.8833,0,0,[[459],[246,251,281,350,457,453,229,341],[143],[193]],[["ghc",6.0642,6.9357]]]
,["Development/Shake/Internal/FileInfo.o",0.0003,0,0,[[460]]]
,["Development/Shake/Internal/FileInfo.hi",0.0007,0,0,[[460]]]
,["Development/Shake/Internal/History/Serialise.deps",0.0068,0,0,[[430],[439,339,451,390,355,459,86]]]
,["Development/Shake/Internal/History/Serialise.o Development/Shake/Internal/History/Serialise.hi",0.9927,0,0,[[463],[245,251,281,350,462,457,442,195,357,453,229,341,393,389],[143],[193]],[["ghc",7.9511,8.9334]]]
,["Development/Shake/Internal/History/Serialise.hi",0.0004,0,0,[[464]]]
,["Development/Shake/Internal/History/Serialise.o",0.0005,0,0,[[464]]]
,["Development/Shake/Internal/History/Server.deps",0.0068,0,0,[[376],[439,463,355,451,339,459,86,221]]]
,["Development/Shake/Internal/History/Server.o Development/Shake/Internal/History/Server.hi",0.5586,0,0,[[467],[243,251,281,350,462,457,442,223,465,195,357,453,229,341,393,389],[143],[193]],[["ghc",8.943,9.4933]]]
,["Development/Shake/Internal/History/Server.hi",0.0005,0,0,[[468]]]
,["Development/Shake/Internal/History/Server.o",0.0005,0,0,[[468]]]
,["Development/Shake/Internal/History/Cloud.deps",0.0065,0,0,[[330],[355,86,221,467,439,272,451,339,333]]]
,["Development/Shake/Internal/History/Cloud.o Development/Shake/Internal/History/Cloud.hi",0.8027,0,0,[[471],[71,251,281,350,462,457,442,223,465,469,195,357,453,229,341,274,393,389,335],[143],[193]],[["ghc",9.5012,10.2923]]]
,["Development/Shake/Internal/History/Cloud.hi",0.0005,0,0,[[472]]]
,["Development/Shake/Internal/History/Cloud.o",0.001,0,0,[[472]]]
,["General/Chunks.deps",0.0086,0,0,[[402],[451,339,227,367]]]
,["General/Chunks.o General/Chunks.hi",0.7743,0,0,[[475],[77,251,281,453,229,341,369],[143],[193]],[["ghc",6.9468,7.7111]]]
,["General/Chunks.hi",0.0008,0,0,[[476]]]
,["General/Chunks.o",0.0003,0,0,[[476]]]
,["Development/Shake/Internal/Core/Storage.deps",0.0071,0,0,[[401],[475,227,451,386,433,347,363,397,390,249,339]]]
,["Development/Shake/Internal/Core/Storage.o Development/Shake/Internal/Core/Storage.hi",0.889,0,0,[[479],[25,251,281,199,350,354,435,453,477,229,341,400,393,389,369,366],[143],[193]],[["ghc",9.0672,9.9391]]]
,["Development/Shake/Internal/Core/Storage.hi",0.0003,0,0,[[480]]]
,["Development/Shake/Internal/Core/Storage.o",0.0004,0,0,[[480]]]
,["Development/Shake/Internal/History/Shared.deps",0.0081,0,0,[[325],[355,86,343,249,451,339,475,459,333,455]]]
,["Development/Shake/Internal/History/Shared.o Development/Shake/Internal/History/Shared.hi",0.856,0,0,[[483],[16,251,281,350,462,457,345,195,357,453,477,229,341,369,335],[143],[193]],[["ghc",7.7229,8.5677]]]
,["Development/Shake/Internal/History/Shared.hi",0.0004,0,0,[[484]]]
,["Development/Shake/Internal/History/Shared.o",0.0006,0,0,[[484]]]
,["Development/Shake/Internal/Core/Types.deps",0.0113,0,0,[[437],[451,339,483,471,86,333,347,214,386,390,371,425,355,433,249,227]]]
,["Development/Shake/Internal/Core/Types.o Development/Shake/Internal/Core/Types.hi",1.3355,0,0,[[487],[10,251,281,199,428,350,462,457,354,442,473,223,465,469,485,345,195,435,357,453,477,229,341,274,393,389,374,369,366,217,335],[143],[193]],[["ghc",10.3035,11.6223]]]
,["Development/Shake/Internal/Core/Types.o",0.0005,0,0,[[488]]]
,["Development/Shake/Internal/Core/Types.hi",0.0004,0,0,[[488]]]
,["Development/Shake/Internal/Profile.deps",0.0051,0,0,[[323],[186,339,347,487,355,390,445,249,386]]]
,["Development/Shake/Internal/Profile.o Development/Shake/Internal/Profile.hi",0.9127,0,0,[[491],[9,251,281,199,428,490,350,462,457,354,442,473,223,465,469,485,345,195,435,447,357,453,477,229,341,274,393,389,374,205,369,366,217,335,310],[143],[193]],[["ghc",11.6373,12.5327]]]
,["Development/Shake/Internal/Profile.hi",0.0005,0,0,[[492]]]
,["Development/Shake/Internal/Profile.o",0.0005,0,0,[[492]]]
,["Development/Shake/Internal/Core/Pool.deps",0.0059,0,0,[[315],[371,487,425,272]]]
,["Development/Shake/Internal/Core/Pool.o Development/Shake/Internal/Core/Pool.hi",0.5991,0,0,[[495],[20,251,281,199,428,490,350,462,457,354,442,473,223,465,469,485,345,195,435,357,453,477,229,341,274,393,389,374,369,366,217,335],[143],[193]],[["ghc",11.6377,12.2258]]]
,["Development/Shake/Internal/Core/Pool.hi",0.0004,0,0,[[496]]]
,["Development/Shake/Internal/Core/Pool.o",0.0007,0,0,[[496]]]
,["Development/Shake/Internal/Progress.deps",0.0064,0,0,[[321],[433,487,186,381,339,445,390]]]
,["Development/Shake/Internal/Progress.o Development/Shake/Internal/Progress.hi",1.0471,0,0,[[499],[125,251,281,199,428,490,350,462,457,354,442,473,223,465,469,485,345,195,435,447,357,453,477,229,384,341,274,393,389,374,205,369,366,217,335,310],[143],[193]],[["ghc",11.6377,12.6697]]]
,["Development/Shake/Internal/Progress.hi",0.0007,0,0,[[500]]]
,["Development/Shake/Internal/Progress.o",0.0003,0,0,[[500]]]
,["Development/Shake/Internal/CompactUI.deps",0.0063,0,0,[[298],[154,433,499,339,367,381]]]
,["Development/Shake/Internal/CompactUI.o Development/Shake/Internal/CompactUI.hi",0.6297,0,0,[[503],[113,251,281,199,428,490,350,462,457,354,442,473,223,465,469,485,345,195,435,447,501,357,453,477,229,384,341,274,393,389,374,205,369,366,217,335,310],[143],[193]],[["ghc",12.6827,13.3019]]]
,["Development/Shake/Internal/CompactUI.o",0.0003,0,0,[[504]]]
,["Development/Shake/Internal/CompactUI.hi",0.0004,0,0,[[504]]]
,["Development/Shake/Internal/Core/Rules.deps",0.0081,0,0,[[431],[249,451,339,214,415,487,425,355,433,347]]]
,["Development/Shake/Internal/Core/Rules.o Development/Shake/Internal/Core/Rules.hi",1.0384,0,0,[[507],[40,251,281,199,428,490,350,462,457,354,442,473,223,465,469,485,345,195,435,357,453,477,229,341,274,393,389,418,374,369,366,217,335],[143],[193]],[["ghc",11.6377,12.6618]]]
,["Development/Shake/Internal/Core/Rules.hi",0.0008,0,0,[[508]]]
,["Development/Shake/Internal/Core/Rules.o",0.0003,0,0,[[508]]]
,["Development/Shake/Internal/Core/Action.deps",0.0094,0,0,[[337],[339,390,386,249,425,483,371,487,507,495,355,459,455,433,347,227,272]]]
,["Development/Shake/Internal/Core/Action.o Development/Shake/Internal/Core/Action.hi",1.2343,0,0,[[511],[263,251,281,199,428,497,509,490,350,462,457,354,442,473,223,465,469,485,345,195,435,357,453,477,229,341,274,393,389,418,374,369,366,217,335],[143],[193]],[["ghc",12.6736,13.8914]]]
,["Development/Shake/Internal/Core/Action.o",0.0007,0,0,[[512]]]
,["Development/Shake/Internal/Core/Action.hi",0.0003,0,0,[[512]]]
,["Development/Shake/Internal/Resource.deps",0.0069,0,0,[[331],[272,420,371,511,487,425,495]]]
,["Development/Shake/Internal/Resource.o Development/Shake/Internal/Resource.hi",0.7486,0,0,[[515],[108,251,281,199,514,428,497,509,490,350,462,457,354,442,473,223,465,469,485,345,195,435,357,422,453,477,229,341,274,393,389,418,374,369,366,217,335],[143],[193]],[["ghc",13.908,14.6456]]]
,["Development/Shake/Internal/Resource.o",0.0003,0,0,[[516]]]
,["Development/Shake/Internal/Resource.hi",0.0003,0,0,[[516]]]
,["Development/Shake/Internal/Core/Run.deps",0.0097,0,0,[[328],[451,249,479,483,471,390,386,214,333,487,511,507,371,499,355,491,433,347,363,367,339,227]]]
,["Development/Shake/Internal/Core/Run.o Development/Shake/Internal/Core/Run.hi",1.1905,0,0,[[519],[141,251,281,199,514,428,497,509,481,490,350,462,457,354,442,473,223,465,469,485,345,195,435,447,493,501,357,453,477,229,384,341,274,400,393,389,418,374,205,369,366,217,335,310],[143],[193]],[["ghc",13.9076,15.08]]]
,["Development/Shake/Internal/Core/Run.hi",0.0004,0,0,[[520]]]
,["Development/Shake/Internal/Core/Run.o",0.0004,0,0,[[520]]]
,["Development/Shake/Internal/Core/Build.deps",0.0083,0,0,[[318],[249,371,355,347,487,511,483,471,433,425,333,339,386,390,507]]]
,["Development/Shake/Internal/Core/Build.o Development/Shake/Internal/Core/Build.hi",1.0772,0,0,[[523],[169,251,281,199,514,428,497,509,490,350,462,457,354,442,473,223,465,469,485,345,195,435,357,453,477,229,341,274,393,389,418,374,369,366,217,335],[143],[193]],[["ghc",13.908,14.9701]]]
,["Development/Shake/Internal/Core/Build.hi",0.0004,0,0,[[524]]]
,["Development/Shake/Internal/Core/Build.o",0.0007,0,0,[[524]]]
,["Development/Shake/Internal/Rules/Oracle.deps",0.0066,0,0,[[314],[487,507,433,523,355,249,451,339]]]
,["Development/Shake/Internal/Rules/Oracle.o Development/Shake/Internal/Rules/Oracle.hi",0.9125,0,0,[[527],[123,251,281,199,514,525,428,497,509,490,350,462,457,354,442,473,223,465,469,485,345,195,435,357,453,477,229,341,274,393,389,418,374,369,366,217,335],[143],[193]],[["ghc",14.9848,15.8686]]]
,["Development/Shake/Internal/Rules/Oracle.o",0.0005,0,0,[[528]]]
,["Development/Shake/Internal/Rules/Oracle.hi",0.0006,0,0,[[528]]]
,["Development/Shake/Internal/Rules/Rerun.deps",0.0067,0,0,[[313],[507,487,523,511,249,451]]]
,["Development/Shake/Internal/Rules/Rerun.o Development/Shake/Internal/Rules/Rerun.hi",0.9982,0,0,[[531],[101,251,281,199,514,525,428,497,509,490,350,462,457,354,442,473,223,465,469,485,345,195,435,357,453,477,229,341,274,393,389,418,374,369,366,217,335],[143],[193]],[["ghc",14.9844,15.9726]]]
,["Development/Shake/Internal/Rules/Rerun.hi",0.0004,0,0,[[532]]]
,["Development/Shake/Internal/Rules/Rerun.o",0.0005,0,0,[[532]]]
,["Development/Shake/Internal/Rules/File.deps",0.0142,0,0,[[394],[451,339,487,507,523,511,455,531,249,278,351,459,433,347]]]
,["Development/Shake/Internal/Rules/File.o Development/Shake/Internal/Rules/File.hi",1.0247,0,0,[[535],[55,251,281,199,514,525,428,497,509,490,350,462,457,354,442,473,223,465,469,485,345,195,435,533,357,453,477,229,341,274,393,389,418,374,369,366,217,335],[143],[193]],[["ghc",15.9807,16.9911]]]
,["Development/Shake/Internal/Rules/File.o",0.0004,0,0,[[536]]]
,["Development/Shake/Internal/Rules/File.hi",0.0004,0,0,[[536]]]
,["Development/Shake/Internal/Rules/OrderOnly.deps",0.0073,0,0,[[316],[487,511,535]]]
,["Development/Shake/Internal/Rules/OrderOnly.o Development/Shake/Internal/Rules/OrderOnly.hi",0.6053,0,0,[[539],[176,251,281,199,514,525,428,497,509,490,350,462,457,354,442,473,223,465,469,485,345,195,435,538,533,357,453,477,229,341,274,393,389,418,374,369,366,217,335],[143],[193]],[["ghc",17.0047,17.6002]]]
,["Development/Shake/Internal/Rules/OrderOnly.o",0.0003,0,0,[[540]]]
,["Development/Shake/Internal/Rules/OrderOnly.hi",0.0005,0,0,[[540]]]
,["Development/Shake/Internal/Derived.deps",0.0097,0,0,[[322],[347,515,487,511,507,433,535,339]]]
,["Development/Shake/Internal/Derived.o Development/Shake/Internal/Derived.hi",0.8974,0,0,[[543],[53,251,281,199,514,525,428,497,509,490,350,462,457,354,442,473,223,465,469,485,345,195,435,518,538,533,357,422,453,477,229,341,274,393,389,418,374,369,366,217,335],[143],[193]],[["ghc",17.0048,17.8887]]]
,["Development/Shake/Internal/Derived.hi",0.0004,0,0,[[544]]]
,["Development/Shake/Internal/Derived.o",0.0005,0,0,[[544]]]
,["Development/Shake/Command.deps",0.007,0,0,[[429],[339,359,154,511,487,278,351,433,535,543]]]
,["Development/Shake/Command.o Development/Shake/Command.hi",1.3214,0,0,[[547],[208,251,281,199,514,525,428,497,509,490,545,350,462,457,354,442,473,223,465,469,485,345,195,435,518,538,533,357,422,453,477,229,341,274,393,389,418,374,362,369,366,217,335],[143],[193]],[["ghc",17.9004,19.2094]]]
,["Development/Shake/Command.o",0.0004,0,0,[[548]]]
,["Development/Shake/Command.hi",0.0003,0,0,[[548]]]
,["Development/Shake/Internal/Demo.deps",0.0056,0,0,[[300],[445,547,339,278]]]
,["Development/Shake/Internal/Demo.o Development/Shake/Internal/Demo.hi",0.8708,0,0,[[551],[145,251,550,281,199,514,525,428,497,509,490,545,350,462,457,354,442,473,223,465,469,485,345,195,435,447,518,538,533,357,422,453,477,229,341,274,393,389,418,374,362,369,366,217,335,310],[143],[193]],[["ghc",19.2207,20.0818]]]
,["Development/Shake/Internal/Demo.hi",0.0004,0,0,[[552]]]
,["Development/Shake/Internal/Demo.o",0.0004,0,0,[[552]]]
,["Development/Shake/Internal/Rules/Files.deps",0.0132,0,0,[[317],[451,511,487,523,507,347,339,455,249,531,535,351,278,459,433]]]
,["Development/Shake/Internal/Rules/Files.o Development/Shake/Internal/Rules/Files.hi",0.997,0,0,[[555],[110,251,281,199,514,525,428,497,509,490,350,462,457,354,442,473,223,465,469,485,345,195,435,538,533,357,453,477,229,341,274,393,389,418,374,369,366,217,335],[143],[193]],[["ghc",17.0044,17.9879]]]
,["Development/Shake/Internal/Rules/Files.hi",0.001,0,0,[[556]]]
,["Development/Shake/Internal/Rules/Files.o",0.0004,0,0,[[556]]]
,["Development/Shake/Internal/Rules/Directory.deps",0.0074,0,0,[[320],[487,511,507,523,355,249,278,351,339,451]]]
,["Development/Shake/Internal/Rules/Directory.o Development/Shake/Internal/Rules/Directory.hi",1.0173,0,0,[[559],[92,251,281,199,514,525,428,497,509,490,350,462,457,354,442,473,223,465,469,485,345,195,435,357,453,477,229,341,274,393,389,418,374,369,366,217,335],[143],[193]],[["ghc",15.0203,15.9896]]]
,["Development/Shake/Internal/Rules/Directory.hi",0.0005,0,0,[[560]]]
,["Development/Shake/Internal/Rules/Directory.o",0.0005,0,0,[[560]]]
,["Development/Shake/Internal/Rules/Default.deps",0.0058,0,0,[[286],[507,559,535,555,531]]]
,["Development/Shake/Internal/Rules/Default.o Development/Shake/Internal/Rules/Default.hi",0.5379,0,0,[[563],[124,251,281,199,514,525,428,497,509,490,350,462,457,354,442,473,223,465,469,485,345,195,435,561,538,557,533,357,453,477,229,341,274,393,389,418,374,369,366,217,335],[143],[193]],[["ghc",17.999,18.5225]]]
,["Development/Shake/Internal/Rules/Default.hi",0.0009,0,0,[[564]]]
,["Development/Shake/Internal/Rules/Default.o",0.0004,0,0,[[564]]]
,["Development/Shake/Database.deps",0.0039,0,0,[[378],[227,347,433,507,519,487,563]]]
,["Development/Shake/Database.o Development/Shake/Database.hi",0.8172,0,0,[[567],[377,251,281,199,514,525,428,497,509,521,481,490,350,462,457,354,442,473,223,465,469,485,345,195,435,447,493,501,565,561,538,557,533,357,453,477,229,384,341,274,400,393,389,418,374,205,369,366,217,335,310],[143],[193]],[["ghc",18.5297,19.3381]]]
,["Development/Shake/Database.o",0.0004,0,0,[[568]]]
,["Development/Shake/Database.hi",0.0003,0,0,[[568]]]
,["Development/Shake/Internal/Args.deps",0.0095,0,0,[[294],[445,433,507,347,503,551,511,278,535,499,567,363,367,234,381]]]
,["Development/Shake/Internal/Args.o Development/Shake/Internal/Args.hi",1.0868,0,0,[[571],[26,251,550,570,281,199,506,514,525,428,497,509,521,481,490,553,545,350,462,457,354,442,473,223,465,469,485,345,195,435,447,493,501,518,565,561,538,557,533,357,422,453,477,229,384,341,274,400,237,393,389,418,374,362,205,369,366,217,335,310],[143],[193]],[["ghc",20.0902,21.1625]]]
,["Development/Shake/Internal/Args.o",0.0004,0,0,[[572]]]
,["Development/Shake/Internal/Args.hi",0.0003,0,0,[[572]]]
,["Development/Shake.deps",0.0108,0,0,[[319],[355,433,487,511,507,515,543,347,499,571,547,351,559,535,555,527,539,531]]]
,["Development/Shake.o Development/Shake.hi",0.6938,0,0,[[575],[149,251,550,570,281,574,199,506,514,525,428,497,509,521,481,490,553,545,350,462,457,354,442,473,223,465,469,485,345,195,435,447,493,501,518,565,561,538,557,530,542,533,357,422,453,477,229,384,341,274,400,237,393,389,418,374,362,205,369,366,217,335,310],[143],[193]],[["ghc",21.1754,21.8577]]]
,["Development/Shake.hi",0.0003,0,0,[[576]]]
,["Development/Shake.o",0.0003,0,0,[[576]]]
,["Development/Ninja/All.deps",0.0084,0,0,[[302],[255,259,409,575,249,339,363,163,455,459,347,535,539]]]
,["Development/Ninja/All.o Development/Ninja/All.hi",1.0557,0,0,[[579],[1,258,408,411,261,577,251,550,570,281,574,199,506,514,525,428,497,509,521,481,490,553,545,350,462,457,354,442,473,223,465,469,485,345,195,435,447,493,501,518,565,561,538,557,530,542,533,357,422,453,477,229,384,341,274,400,237,393,389,418,201,374,362,205,369,366,217,335,310],[143],[193]],[["ghc",21.8681,22.9021]]]
,["Development/Ninja/All.hi",0.0003,0,0,[[580]]]
,["Development/Ninja/All.o",0.0005,0,0,[[580]]]
,["Run.deps",0.006,0,0,[[299],[579,575,278,363,339,234]]]
,["Run.o Run.hi",0.7432,0,0,[[583],[70,581,258,408,411,261,577,251,550,570,281,574,199,506,514,525,428,497,509,521,481,490,553,545,350,462,457,354,442,473,223,465,469,485,345,195,435,447,493,501,518,565,561,538,557,530,542,533,357,422,453,477,229,384,341,274,400,237,393,389,418,201,374,362,205,369,366,217,335,310],[143],[193]],[["ghc",22.916,23.6482]]]
,["Run.o",0.0003,0,0,[[584]]]
,["Main.exe",3.8846,0,0,[[583],[585,582,257,407,412,262,578,252,549,569,280,573,198,505,513,526,427,498,510,522,482,489,554,546,349,461,458,353,441,474,224,466,470,486,346,196,436,448,494,502,517,566,562,537,558,529,541,534,358,423,454,478,230,383,342,275,399,236,392,388,417,202,373,361,204,370,365,216,336,309],[143],[193]],[["ghc",23.6565,27.5353]]]
,["Root",0,0,0,[[586]],[["",27.538,27.538]]]
]

View File

@ -0,0 +1,183 @@
var progress =
[{"name":"self-zero-j2.prog", "values":
[{"idealSecs":76.7, "idealPerc":1.3, "actualSecs":195.6, "actualPerc":0.5}
,{"idealSecs":74.0, "idealPerc":4.8, "actualSecs":563.2, "actualPerc":0.7}
,{"idealSecs":72.7, "idealPerc":6.5, "actualSecs":183.8, "actualPerc":2.5}
,{"idealSecs":71.4, "idealPerc":8.2, "actualSecs":130.9, "actualPerc":4.3}
,{"idealSecs":70.1, "idealPerc":9.8, "actualSecs":109.3, "actualPerc":6.1}
,{"idealSecs":68.8, "idealPerc":11.4, "actualSecs":97.2, "actualPerc":7.8}
,{"idealSecs":67.6, "idealPerc":13.0, "actualSecs":89.6, "actualPerc":9.6}
,{"idealSecs":66.3, "idealPerc":14.7, "actualSecs":84.0, "actualPerc":11.3}
,{"idealSecs":65.0, "idealPerc":16.3, "actualSecs":79.6, "actualPerc":13.0}
,{"idealSecs":63.8, "idealPerc":17.9, "actualSecs":75.9, "actualPerc":14.8}
,{"idealSecs":62.5, "idealPerc":19.6, "actualSecs":72.7, "actualPerc":16.5}
,{"idealSecs":61.2, "idealPerc":21.2, "actualSecs":70.0, "actualPerc":18.2}
,{"idealSecs":60.0, "idealPerc":22.8, "actualSecs":67.5, "actualPerc":20.0}
,{"idealSecs":58.7, "idealPerc":24.5, "actualSecs":65.1, "actualPerc":21.8}
,{"idealSecs":57.4, "idealPerc":26.1, "actualSecs":62.5, "actualPerc":23.6}
,{"idealSecs":56.2, "idealPerc":27.7, "actualSecs":60.5, "actualPerc":25.4}
,{"idealSecs":54.9, "idealPerc":29.3, "actualSecs":58.6, "actualPerc":27.1}
,{"idealSecs":53.6, "idealPerc":31.0, "actualSecs":57.0, "actualPerc":28.8}
,{"idealSecs":52.1, "idealPerc":32.9, "actualSecs":55.0, "actualPerc":30.9}
,{"idealSecs":50.5, "idealPerc":35.0, "actualSecs":53.6, "actualPerc":32.8}
,{"idealSecs":49.3, "idealPerc":36.6, "actualSecs":51.5, "actualPerc":34.7}
,{"idealSecs":48.0, "idealPerc":38.2, "actualSecs":49.4, "actualPerc":36.7}
,{"idealSecs":46.7, "idealPerc":39.8, "actualSecs":47.8, "actualPerc":38.5}
,{"idealSecs":45.5, "idealPerc":41.5, "actualSecs":46.2, "actualPerc":40.2}
,{"idealSecs":44.2, "idealPerc":43.1, "actualSecs":44.7, "actualPerc":42.0}
,{"idealSecs":43.2, "idealPerc":44.4, "actualSecs":44.7, "actualPerc":42.0}
,{"idealSecs":41.9, "idealPerc":46.1, "actualSecs":42.6, "actualPerc":44.9}
,{"idealSecs":40.7, "idealPerc":47.7, "actualSecs":40.0, "actualPerc":47.3}
,{"idealSecs":39.4, "idealPerc":49.3, "actualSecs":38.5, "actualPerc":49.1}
,{"idealSecs":38.1, "idealPerc":51.0, "actualSecs":37.1, "actualPerc":50.9}
,{"idealSecs":36.7, "idealPerc":52.8, "actualSecs":35.7, "actualPerc":52.8}
,{"idealSecs":35.4, "idealPerc":54.4, "actualSecs":33.8, "actualPerc":54.9}
,{"idealSecs":34.2, "idealPerc":56.0, "actualSecs":32.3, "actualPerc":56.7}
,{"idealSecs":32.4, "idealPerc":58.3, "actualSecs":29.1, "actualPerc":60.2}
,{"idealSecs":31.4, "idealPerc":59.6, "actualSecs":29.1, "actualPerc":60.2}
,{"idealSecs":29.7, "idealPerc":61.7, "actualSecs":28.0, "actualPerc":62.6}
,{"idealSecs":28.5, "idealPerc":63.4, "actualSecs":28.0, "actualPerc":62.6}
,{"idealSecs":27.2, "idealPerc":65.0, "actualSecs":27.4, "actualPerc":64.4}
,{"idealSecs":26.0, "idealPerc":66.6, "actualSecs":24.8, "actualPerc":67.2}
,{"idealSecs":24.7, "idealPerc":68.2, "actualSecs":23.3, "actualPerc":69.0}
,{"idealSecs":23.4, "idealPerc":69.9, "actualSecs":21.9, "actualPerc":70.8}
,{"idealSecs":22.1, "idealPerc":71.5, "actualSecs":20.5, "actualPerc":72.7}
,{"idealSecs":20.8, "idealPerc":73.2, "actualSecs":18.7, "actualPerc":74.9}
,{"idealSecs":19.5, "idealPerc":74.9, "actualSecs":17.3, "actualPerc":76.7}
,{"idealSecs":18.2, "idealPerc":76.5, "actualSecs":15.5, "actualPerc":79.0}
,{"idealSecs":16.5, "idealPerc":78.7, "actualSecs":12.8, "actualPerc":82.4}
,{"idealSecs":15.5, "idealPerc":80.0, "actualSecs":12.8, "actualPerc":82.4}
,{"idealSecs":13.9, "idealPerc":82.1, "actualSecs":11.7, "actualPerc":84.3}
,{"idealSecs":10.4, "idealPerc":86.6, "actualSecs":10.9, "actualPerc":85.9}
,{"idealSecs":8.6, "idealPerc":89.0, "actualSecs":7.1, "actualPerc":90.5}
,{"idealSecs":6.8, "idealPerc":91.3, "actualSecs":5.9, "actualPerc":92.2}
,{"idealSecs":5.0, "idealPerc":93.5, "actualSecs":4.8, "actualPerc":93.8}
,{"idealSecs":4.0, "idealPerc":94.8, "actualSecs":4.8, "actualPerc":93.8}
,{"idealSecs":3.0, "idealPerc":96.1, "actualSecs":4.8, "actualPerc":93.8}
,{"idealSecs":2.0, "idealPerc":97.4, "actualSecs":4.8, "actualPerc":93.8}
,{"idealSecs":1.0, "idealPerc":98.7, "actualSecs":4.8, "actualPerc":93.8}
,{"idealSecs":0.0, "idealPerc":100.0, "actualSecs":4.8, "actualPerc":93.8}
]
},{"name":"self-rebuild-j2.prog", "values":
[{"idealSecs":79.3, "idealPerc":4.3, "actualSecs":461.8, "actualPerc":0.8}
,{"idealSecs":78.0, "idealPerc":5.9, "actualSecs":164.3, "actualPerc":2.7}
,{"idealSecs":76.7, "idealPerc":7.5, "actualSecs":117.9, "actualPerc":4.6}
,{"idealSecs":75.5, "idealPerc":9.0, "actualSecs":99.1, "actualPerc":6.5}
,{"idealSecs":74.2, "idealPerc":10.5, "actualSecs":88.3, "actualPerc":8.4}
,{"idealSecs":72.9, "idealPerc":12.1, "actualSecs":66.6, "actualPerc":12.1}
,{"idealSecs":71.6, "idealPerc":13.6, "actualSecs":66.6, "actualPerc":12.1}
,{"idealSecs":70.3, "idealPerc":15.2, "actualSecs":72.7, "actualPerc":14.0}
,{"idealSecs":69.1, "idealPerc":16.7, "actualSecs":69.2, "actualPerc":15.9}
,{"idealSecs":67.8, "idealPerc":18.3, "actualSecs":66.3, "actualPerc":17.8}
,{"idealSecs":66.5, "idealPerc":19.8, "actualSecs":63.7, "actualPerc":19.7}
,{"idealSecs":65.2, "idealPerc":21.4, "actualSecs":61.2, "actualPerc":21.6}
,{"idealSecs":63.9, "idealPerc":22.9, "actualSecs":59.2, "actualPerc":23.5}
,{"idealSecs":62.6, "idealPerc":24.5, "actualSecs":57.2, "actualPerc":25.4}
,{"idealSecs":61.3, "idealPerc":26.1, "actualSecs":55.1, "actualPerc":27.3}
,{"idealSecs":59.2, "idealPerc":28.6, "actualSecs":54.0, "actualPerc":29.7}
,{"idealSecs":57.9, "idealPerc":30.2, "actualSecs":51.2, "actualPerc":32.0}
,{"idealSecs":56.6, "idealPerc":31.7, "actualSecs":49.5, "actualPerc":33.8}
,{"idealSecs":55.4, "idealPerc":33.2, "actualSecs":47.7, "actualPerc":35.8}
,{"idealSecs":53.4, "idealPerc":35.6, "actualSecs":46.1, "actualPerc":38.2}
,{"idealSecs":51.8, "idealPerc":37.5, "actualSecs":43.7, "actualPerc":40.8}
,{"idealSecs":50.5, "idealPerc":39.1, "actualSecs":41.9, "actualPerc":42.8}
,{"idealSecs":49.3, "idealPerc":40.6, "actualSecs":40.3, "actualPerc":44.7}
,{"idealSecs":48.0, "idealPerc":42.2, "actualSecs":38.8, "actualPerc":46.6}
,{"idealSecs":46.7, "idealPerc":43.7, "actualSecs":37.3, "actualPerc":48.5}
,{"idealSecs":45.4, "idealPerc":45.3, "actualSecs":35.9, "actualPerc":50.3}
,{"idealSecs":44.0, "idealPerc":47.0, "actualSecs":34.5, "actualPerc":52.3}
,{"idealSecs":42.6, "idealPerc":48.6, "actualSecs":33.0, "actualPerc":54.3}
,{"idealSecs":41.3, "idealPerc":50.2, "actualSecs":31.5, "actualPerc":56.3}
,{"idealSecs":39.9, "idealPerc":51.8, "actualSecs":30.1, "actualPerc":58.2}
,{"idealSecs":38.7, "idealPerc":53.4, "actualSecs":28.7, "actualPerc":60.0}
,{"idealSecs":37.1, "idealPerc":55.3, "actualSecs":27.8, "actualPerc":61.6}
,{"idealSecs":36.1, "idealPerc":56.5, "actualSecs":26.2, "actualPerc":63.5}
,{"idealSecs":35.1, "idealPerc":57.7, "actualSecs":26.2, "actualPerc":63.5}
,{"idealSecs":32.1, "idealPerc":61.3, "actualSecs":26.1, "actualPerc":65.7}
,{"idealSecs":30.1, "idealPerc":63.7, "actualSecs":24.8, "actualPerc":67.7}
,{"idealSecs":28.8, "idealPerc":65.3, "actualSecs":22.1, "actualPerc":70.6}
,{"idealSecs":27.5, "idealPerc":66.8, "actualSecs":20.7, "actualPerc":72.4}
,{"idealSecs":26.5, "idealPerc":68.0, "actualSecs":19.2, "actualPerc":74.2}
,{"idealSecs":23.9, "idealPerc":71.2, "actualSecs":18.4, "actualPerc":75.9}
,{"idealSecs":22.6, "idealPerc":72.8, "actualSecs":17.0, "actualPerc":77.7}
,{"idealSecs":21.3, "idealPerc":74.3, "actualSecs":15.4, "actualPerc":79.8}
,{"idealSecs":20.0, "idealPerc":75.9, "actualSecs":14.0, "actualPerc":81.6}
,{"idealSecs":17.8, "idealPerc":78.5, "actualSecs":11.6, "actualPerc":84.6}
,{"idealSecs":16.8, "idealPerc":79.7, "actualSecs":11.6, "actualPerc":84.6}
,{"idealSecs":15.3, "idealPerc":81.6, "actualSecs":10.5, "actualPerc":86.4}
,{"idealSecs":11.7, "idealPerc":85.9, "actualSecs":9.7, "actualPerc":88.0}
,{"idealSecs":10.7, "idealPerc":87.1, "actualSecs":7.9, "actualPerc":90.1}
,{"idealSecs":9.4, "idealPerc":88.7, "actualSecs":6.3, "actualPerc":92.0}
,{"idealSecs":7.2, "idealPerc":91.3, "actualSecs":4.7, "actualPerc":94.1}
,{"idealSecs":5.0, "idealPerc":93.9, "actualSecs":3.8, "actualPerc":95.3}
,{"idealSecs":4.0, "idealPerc":95.2, "actualSecs":3.8, "actualPerc":95.3}
,{"idealSecs":3.0, "idealPerc":96.4, "actualSecs":3.8, "actualPerc":95.3}
,{"idealSecs":2.0, "idealPerc":97.6, "actualSecs":3.8, "actualPerc":95.3}
,{"idealSecs":1.0, "idealPerc":98.8, "actualSecs":3.8, "actualPerc":95.3}
,{"idealSecs":0.0, "idealPerc":100.0, "actualSecs":3.8, "actualPerc":95.3}
]
},{"name":"self-clean-j2.prog", "values":
[{"idealSecs":87.2, "idealPerc":1.3, "actualSecs":0.6, "actualPerc":63.7}
,{"idealSecs":85.8, "idealPerc":2.8, "actualSecs":4.8, "actualPerc":35.3}
,{"idealSecs":83.1, "idealPerc":5.8, "actualSecs":21.5, "actualPerc":19.1}
,{"idealSecs":81.8, "idealPerc":7.3, "actualSecs":27.1, "actualPerc":18.5}
,{"idealSecs":80.6, "idealPerc":8.8, "actualSecs":33.1, "actualPerc":18.1}
,{"idealSecs":79.2, "idealPerc":10.3, "actualSecs":32.8, "actualPerc":20.7}
,{"idealSecs":77.9, "idealPerc":11.7, "actualSecs":38.2, "actualPerc":20.4}
,{"idealSecs":76.6, "idealPerc":13.2, "actualSecs":38.1, "actualPerc":22.5}
,{"idealSecs":75.3, "idealPerc":14.7, "actualSecs":41.0, "actualPerc":23.0}
,{"idealSecs":74.1, "idealPerc":16.1, "actualSecs":38.6, "actualPerc":25.9}
,{"idealSecs":72.8, "idealPerc":17.6, "actualSecs":39.4, "actualPerc":27.3}
,{"idealSecs":71.5, "idealPerc":19.0, "actualSecs":43.4, "actualPerc":27.0}
,{"idealSecs":70.2, "idealPerc":20.5, "actualSecs":40.1, "actualPerc":30.1}
,{"idealSecs":68.9, "idealPerc":22.0, "actualSecs":35.9, "actualPerc":34.1}
,{"idealSecs":66.8, "idealPerc":24.3, "actualSecs":41.6, "actualPerc":33.1}
,{"idealSecs":65.5, "idealPerc":25.8, "actualSecs":43.5, "actualPerc":33.4}
,{"idealSecs":64.2, "idealPerc":27.3, "actualSecs":46.4, "actualPerc":33.3}
,{"idealSecs":62.7, "idealPerc":28.9, "actualSecs":40.7, "actualPerc":37.7}
,{"idealSecs":61.4, "idealPerc":30.4, "actualSecs":43.5, "actualPerc":37.3}
,{"idealSecs":60.1, "idealPerc":32.0, "actualSecs":46.1, "actualPerc":37.2}
,{"idealSecs":58.8, "idealPerc":33.4, "actualSecs":46.4, "actualPerc":38.1}
,{"idealSecs":57.5, "idealPerc":34.9, "actualSecs":48.6, "actualPerc":38.0}
,{"idealSecs":56.5, "idealPerc":36.1, "actualSecs":48.6, "actualPerc":38.0}
,{"idealSecs":55.2, "idealPerc":37.5, "actualSecs":50.1, "actualPerc":39.2}
,{"idealSecs":53.8, "idealPerc":39.0, "actualSecs":53.4, "actualPerc":38.5}
,{"idealSecs":52.5, "idealPerc":40.5, "actualSecs":37.4, "actualPerc":48.1}
,{"idealSecs":51.2, "idealPerc":42.0, "actualSecs":39.2, "actualPerc":47.9}
,{"idealSecs":49.9, "idealPerc":43.5, "actualSecs":30.8, "actualPerc":54.8}
,{"idealSecs":48.6, "idealPerc":45.0, "actualSecs":28.5, "actualPerc":57.6}
,{"idealSecs":46.6, "idealPerc":47.2, "actualSecs":28.3, "actualPerc":58.9}
,{"idealSecs":45.3, "idealPerc":48.7, "actualSecs":27.5, "actualPerc":60.4}
,{"idealSecs":43.9, "idealPerc":50.2, "actualSecs":26.3, "actualPerc":62.2}
,{"idealSecs":42.9, "idealPerc":51.4, "actualSecs":24.9, "actualPerc":64.0}
,{"idealSecs":41.2, "idealPerc":53.3, "actualSecs":23.9, "actualPerc":65.8}
,{"idealSecs":40.2, "idealPerc":54.4, "actualSecs":23.9, "actualPerc":65.8}
,{"idealSecs":38.4, "idealPerc":56.5, "actualSecs":23.5, "actualPerc":67.6}
,{"idealSecs":37.4, "idealPerc":57.6, "actualSecs":23.5, "actualPerc":67.6}
,{"idealSecs":36.4, "idealPerc":58.8, "actualSecs":23.5, "actualPerc":67.6}
,{"idealSecs":33.4, "idealPerc":62.2, "actualSecs":24.5, "actualPerc":69.0}
,{"idealSecs":32.1, "idealPerc":63.7, "actualSecs":25.2, "actualPerc":68.9}
,{"idealSecs":30.8, "idealPerc":65.2, "actualSecs":25.0, "actualPerc":69.5}
,{"idealSecs":29.5, "idealPerc":66.6, "actualSecs":25.4, "actualPerc":69.6}
,{"idealSecs":28.2, "idealPerc":68.1, "actualSecs":19.1, "actualPerc":75.7}
,{"idealSecs":26.3, "idealPerc":70.3, "actualSecs":19.9, "actualPerc":75.5}
,{"idealSecs":25.0, "idealPerc":71.7, "actualSecs":18.2, "actualPerc":77.5}
,{"idealSecs":23.7, "idealPerc":73.2, "actualSecs":17.3, "actualPerc":78.7}
,{"idealSecs":22.4, "idealPerc":74.7, "actualSecs":13.6, "actualPerc":82.7}
,{"idealSecs":20.2, "idealPerc":77.2, "actualSecs":8.8, "actualPerc":88.5}
,{"idealSecs":19.2, "idealPerc":78.3, "actualSecs":8.8, "actualPerc":88.5}
,{"idealSecs":17.5, "idealPerc":80.2, "actualSecs":7.5, "actualPerc":90.4}
,{"idealSecs":13.9, "idealPerc":84.2, "actualSecs":6.1, "actualPerc":92.4}
,{"idealSecs":12.9, "idealPerc":85.4, "actualSecs":4.6, "actualPerc":94.3}
,{"idealSecs":11.4, "idealPerc":87.0, "actualSecs":3.1, "actualPerc":96.1}
,{"idealSecs":9.2, "idealPerc":89.6, "actualSecs":1.6, "actualPerc":98.1}
,{"idealSecs":7.0, "idealPerc":92.0, "actualSecs":0.5, "actualPerc":99.4}
,{"idealSecs":6.0, "idealPerc":93.2, "actualSecs":0.5, "actualPerc":99.4}
,{"idealSecs":5.0, "idealPerc":94.3, "actualSecs":0.5, "actualPerc":99.4}
,{"idealSecs":4.0, "idealPerc":95.4, "actualSecs":0.5, "actualPerc":99.4}
,{"idealSecs":3.0, "idealPerc":96.6, "actualSecs":0.5, "actualPerc":99.4}
,{"idealSecs":2.0, "idealPerc":97.7, "actualSecs":0.5, "actualPerc":99.4}
,{"idealSecs":1.0, "idealPerc":98.9, "actualSecs":0.5, "actualPerc":99.4}
,{"idealSecs":0.0, "idealPerc":100.0, "actualSecs":0.5, "actualPerc":99.4}
]
}]

211
hls-graph/html/profile.html Normal file
View File

@ -0,0 +1,211 @@
<!DOCTYPE html>
<html lang="en">
<head>
<meta charset="utf-8" />
<title>Shake report</title>
<!-- Profiling output -->
<script src="data/profile-data.js"></script>
<script src="data/build-data.js"></script>
<script src="data/metadata.js"></script>
<!-- Libraries -->
<script src="lib/jquery.js"></script>
<script src="lib/jquery.flot.js"></script>
<script src="lib/jquery.flot.stack.js"></script>
<script src="lib/jquery.dgtable.js"></script>
<!-- Functions for creating info from Shake builds -->
<script src="shake.js"></script>
<style type="text/css">
body {font-family: sans-serif; font-size: 10pt; background-color: #e8e8e8;}
.data {font-size: 9pt; border-spacing: 0px; border-collapse: collapse;}
.data td {padding-left: 7px; padding-right: 7px;}
.header {font-weight: bold; background-color: #eee !important;}
.header td:hover {background-color: #ccc !important;}
.header td {border: 1px solid #ccc; cursor: pointer;}
.data tr:hover {background-color: #ddd !important; color: black !important;}
* {box-sizing: border-box;}
html, body, .fill {height: 100%; width:100%;}
table.fill {border-spacing: 0px;}
input:focus {border-color: rgb(77, 144, 254) !important; outline-width: 0px !important;}
.note {margin-left: 10px;}
.note, .note a {color: gray;}
a tt {color: #315273;}
.tabstrip a {
border-radius: 4px 4px 0px 0px;
border: 1px solid gray;
padding: 4px 8px;
box-sizing: border-box;
cursor: pointer;
white-space: nowrap;
user-select: none;
}
.tabstrip .bottom {
padding: 4px 8px;
border-bottom: 1px solid gray;
}
.tabstrip .active {
border-top: 4px solid orange;
border-bottom: 3px solid white;
background-color: white;
}
.right { text-align: right; }
.dropdown {
border:1px solid gray;
background-color:white;
white-space:nowrap;
position:absolute;
right:10px;
padding-right:10px;
box-shadow: 3px 3px 5px #ccc;
z-index: 100;
}
.dropdown a tt {
cursor: pointer;
color: #1467bb !important;
}
.details a {
cursor: pointer;
color: #1467bb;
}
/* My overrides */
/* Make the colors and font size match better */
.dgtable-row:hover { background-color: #e8e8e8 !important; }
.dgtable-header-cell:hover { background-color: #ddd !important; }
.dgtable-header-cell { background-color: #eee !important; }
.dgtable-cell:last-child, .dgtable-header-cell:last-child { border-right: 1px solid #ccc; }
/* Make the header smaller */
.dgtable-header-row, .dgtable-header-cell { height: 22px !important; }
.dgtable-header-cell { padding: 2px 4px !important; }
.dgtable-header-cell, .dgtable-cell-preview.header { font-size: 9pt !important; }
/* Make the rows smaller */
.dgtable-row { height: 22px !important; }
.dgtable-row:first-child { height: 23px !important; }
.dgtable-cell { padding: 2px 4px !important; height: 22px !important; }
.dgtable-cell, .dgtable-cell-preview{ font-size: 9pt !important; }
.dgtable-wrapper * {
box-sizing: border-box;
}
.dgtable-wrapper {
border: solid 1px #ccc;
}
.dgtable {
border-top: solid 1px #ccc;
max-width: 100%;
background-color: transparent;
}
.dgtable-header {
max-width: 100%;
overflow: hidden;
background: #eee;
}
.dgtable-header-row {
height: 26px;
}
.dgtable-header-cell {
float: left;
padding: 4px;
height: 26px;
border-left: solid 1px #ccc;
background: #ddd;
font-size: 13px;
line-height: 16px;
font-weight: bold;
cursor: default;
text-align: left;
}
.dgtable-header-cell:first-child {
border-left: 0;
}
.dgtable-header-cell > div {
border: 1px dashed transparent;
white-space: nowrap;
overflow-x: hidden;
text-overflow: ellipsis;
}
.dgtable-header-cell.drag-over > div {
border-color: #666;
background: #bbb;
}
.dgtable-row {
border-top: solid 1px #ccc;
height: 28px;
}
.dgtable-row:first-child {
border-top: 0;
height: 29px;
}
.dgtable.virtual .dgtable-row {
border-top: 0;
border-bottom: solid 1px #ccc;
}
.dgtable-cell {
float: left;
padding: 4px 4px 4px;
height: 28px;
border-left: solid 1px #ccc;
font-size: 16px;
line-height: 19px;
}
.dgtable-cell > div {
max-height: 100%;
white-space: nowrap;
overflow: hidden
}
.dgtable-cell:first-child {
border-left: 0;
}
.dgtable-header-cell.sortable {
cursor: pointer;
}
.dgtable-header-cell.sorted .sort-arrow {
float: right;
display: inline-block;
width: 15px;
height: 6px;
margin: 5px 0 0 0;
background: url("data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAsAAAAGCAMAAAAi7JTKAAAAIGNIUk0AAHolAACAgwAA+f8AAIDpAAB1MAAA6mAAADqYAAAXb5JfxUYAAAMAUExURQNOov///wAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAH52dxwAAAACdFJOU/8A5bcwSgAAAAlwSFlzAAALEwAACxMBAJqcGAAAAB9JREFUCB0FwQEBAAAAgJD8Px0VoFKgRKEIpRBUEAgMBlQAL3y6umEAAAAASUVORK5CYII=") no-repeat center center;
}
.dgtable-header-cell.sorted.desc .sort-arrow {
background-image: url("data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAsAAAAGCAMAAAAi7JTKAAAAIGNIUk0AAHolAACAgwAA+f8AAIDpAAB1MAAA6mAAADqYAAAXb5JfxUYAAAMAUExURQNOov///wAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAH52dxwAAAACdFJOU/8A5bcwSgAAAAlwSFlzAAALEwAACxMBAJqcGAAAAB9JREFUCB0FwQEBAAAAgJD8Px2BQFBBKIUoFClQKkANBywAL6PcDsUAAAAASUVORK5CYII=");
}
.dgtable-cell-preview {
font-size: 16px;
line-height: 19px;
}
/* Making the cell preview show correct styling when previewing header cells */
.dgtable-cell-preview.header {
font-size: 13px;
line-height: 16px;
font-weight: bold;
text-align: left;
}
.dgtable-cell-preview.header > div {
border: 1px dashed transparent;
}
.dgtable-cell-preview.header.sortable {
cursor: pointer;
}
.dgtable-cell-preview.header.drag-over > div {
border-color: #666;
background: #bbb;
}
</style>
</head>
<body style="margin:0px;padding:0px;" onload="profileLoaded(profile, build)">
Loading...
</body>
</html>

1058
hls-graph/html/shake.js Normal file

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,77 @@
function bindPlot(element: HTMLElement, data: Prop<jquery.flot.dataSeries[]>, options: jquery.flot.plotOptions): void {
const redraw = () => {
if ($(element).is(":visible"))
$.plot($(element), data.get(), options);
};
window.setTimeout(redraw, 1);
$(window).on("resize", redraw);
data.event(redraw);
}
function varLink(name: string): HTMLElement {
return <a href={"https://hackage.haskell.org/package/shake/docs/Development-Shake.html#v:" + name}><tt>{name}</tt></a>;
}
interface Column {
field: string;
label: string;
width: int;
alignRight?: boolean;
show?: (x: any) => string;
}
// A simple approximation of what DGTable provides
declare class DGTable {
public static Width: {SCROLL: void};
public el: HTMLElement;
constructor(options: any);
public setRows(rows: object[], resort: boolean): void;
public render(): void;
public tableHeightChanged(): void;
public sort(x: string, descending: boolean): void;
}
function newTable(columns: Column[], data: Prop<object[]>, sortColumn?: string, sortDescend?: boolean): HTMLElement {
const f = (x: Column) => ({name: x.field, label: x.label, width: x.width, cellClasses: x.alignRight ? "right" : ""});
const formatters = {};
for (const c of columns)
formatters[c.field] = c.show || ((x: any) => x);
const table = new DGTable({
adjustColumnWidthForSortArrow: false,
cellFormatter: (val: any, colname: string) => formatters[colname](val),
columns: columns.map(f),
width: DGTable.Width.SCROLL
});
$(table.el).css("height", "100%");
window.setTimeout(() => {
table.render();
table.tableHeightChanged();
if (sortColumn)
table.sort(sortColumn, sortDescend);
table.setRows(data.get(), true);
}, 1);
let toRender = false;
data.event(xs => {
table.setRows(xs, true);
if ($(table.el).is(":visible"))
table.render();
else
toRender = true;
});
$(window).on("resize", () => {
if ($(table.el).is(":visible")) {
table.tableHeightChanged();
if (toRender) {
table.render();
toRender = false;
}
}
});
return <div style="height:100%;width:100%;">{table.el}</div>;
}

View File

@ -0,0 +1,87 @@
// These are global variables mutated/queried by query execution
let environmentAll: Profile[]; // All the profiles
let environmentThis: Profile; // The specific profile under test
let environmentGroup: string[]; // The group produced as a result
function group(x: string): boolean {
environmentGroup.push(x);
return true;
}
function leaf(): boolean {
return environmentThis.depends.length === 0;
}
function run(): number;
function run(i: timestamp): boolean;
function run(i?: timestamp): number | boolean {
if (i === undefined)
return environmentThis.built;
else
return environmentThis.built === i;
}
function changed(): boolean {
return environmentThis.changed === environmentThis.built;
}
function visited(): number;
function visited(i:timestamp): boolean;
function visited(i?: timestamp): number | boolean {
if(i === undefined)
return environmentThis.visited;
else
return environmentThis.visited === i;
}
function unchanged(): boolean {
return !unchanged();
}
function named(): string;
function named(r: string | RegExp, groupName?: string): boolean;
function /* export */ named(r?: string | RegExp, groupName?: string): string | boolean {
if (r === undefined)
return environmentThis.name;
const res = execRegExp(r, environmentThis.name);
if (res === null) {
if (groupName === undefined)
return false;
else {
group(groupName);
return true;
}
}
if (res.length !== 1) {
for (let i = 1; i < res.length; i++)
group(res[i]);
}
return true;
}
function command(): string;
function command(r: string | RegExp, groupName?: string): boolean;
function /* export */ command(r?: any, groupName?: any): any {
const n = (environmentThis.traces || []).length;
if (r === undefined)
return n === 0 ? "" : environmentThis.traces[0].command;
for (const t of environmentThis.traces) {
const res = execRegExp(r, t.command);
if (res === null)
continue;
if (res.length !== 1) {
for (let j = 1; j < res.length; j++)
group(res[j]);
}
return true;
}
if (groupName === undefined)
return false;
else {
group(groupName);
return true;
}
}

3190
hls-graph/html/ts/jquery.d.ts vendored Normal file

File diff suppressed because it is too large Load Diff

240
hls-graph/html/ts/jquery.flot.d.ts vendored Normal file
View File

@ -0,0 +1,240 @@
// Type definitions for Flot
// Project: http://www.flotcharts.org/
// Definitions by: Matt Burland <https://github.com/burlandm>
// Definitions: https://github.com/borisyankov/DefinitelyTyped
declare module jquery.flot {
interface plotOptions {
colors?: any[];
series?: seriesOptions;
legend?: legendOptions;
xaxis?: axisOptions;
yaxis?: axisOptions;
xaxes?: axisOptions[];
yaxes?: axisOptions[];
grid?: gridOptions;
interaction?: interaction;
hooks?: hooks;
}
interface hooks {
processOptions: { (plot: plot, options: plotOptions): void; } [];
processRawData: { (plot: plot, series: dataSeries, data: any[], datapoints: datapoints): void; }[];
processDatapoints: { (plot: plot, series: dataSeries, datapoints: datapoints): void; }[];
processOffset: { (plot: plot, offset: canvasPoint): void; }[];
drawBackground: { (plot: plot, context: CanvasRenderingContext2D): void; }[];
drawSeries: { (plot: plot, context: CanvasRenderingContext2D, series: dataSeries): void; }[];
draw: { (plot: plot, context: CanvasRenderingContext2D): void; }[];
bindEvents: { (plot: plot, eventHolder: JQuery): void; }[];
drawOverlay: { (plot: plot, context: CanvasRenderingContext2D): void; }[];
shutdown: { (plot: plot, eventHolder: JQuery): void; }[];
}
interface interaction {
redrawOverlayInterval?: number;
}
interface gridOptions {
show?: boolean;
aboveData?: boolean;
color?: any; // color
backgroundColor?: any; //color/gradient or null
margin?: any; // number or margin object
labelMargin?: number;
axisMargin?: number;
markings?: any; //array of markings or (fn: axes -> array of markings)
borderWidth?: any; // number or width object
borderColor?: any; // color or null
minBorderMargin?: number; // or null
clickable?: boolean;
hoverable?: boolean;
autoHighlight?: boolean;
mouseActiveRadius?: number;
tickColor?: any;
markingsColor?: any;
markingsLineWidth?: number;
}
interface legendOptions {
show?: boolean;
labelFormatter?: (label: string, series: any) => string; // null or (fn: string, series object -> string)
labelBoxBorderColor?: any; //color
noColumns?: number;
position?: string; //"ne" or "nw" or "se" or "sw"
margin?: any; //number of pixels or [x margin, y margin]
backgroundColor?: any; //null or color
backgroundOpacity?: number; // between 0 and 1
container?: JQuery; // null or jQuery object/DOM element/jQuery expression
sorted?: any; //null/false, true, "ascending", "descending" or a comparator
}
interface seriesOptions {
color?: any; // color or number
label?: string;
lines?: linesOptions;
bars?: barsOptions;
points?: pointsOptions;
xaxis?: number;
yaxis?: number;
clickable?: boolean;
hoverable?: boolean;
shadowSize?: number;
highlightColor?: any;
stack?: boolean; // NEIL: Since we use the Stack plugin
}
interface dataSeries extends seriesOptions {
data: any[];
}
interface axisOptions {
show?: boolean; // null or true/false
position?: string; // "bottom" or "top" or "left" or "right"
color?: any; // null or color spec
tickColor?: any; // null or color spec
font?: any; // null or font spec object
min?: number;
max?: number;
autoscaleMargin?: number;
transform?: (v: number) => number; // null or fn: number -> number
inverseTransform?: (v: number) => number; // null or fn: number -> number
ticks?: any; // null or number or ticks array or (fn: axis -> ticks array)
tickSize?: any; // number or array
minTickSize?: any; // number or array
tickFormatter?: (t: number, a?: axis) => string; // (fn: number, object -> string) or string
tickDecimals?: number;
labelWidth?: number;
labelHeight?: number;
reserveSpace?: boolean;
tickLength?: number;
alignTicksWithAxis?: number;
}
interface seriesTypeBase {
show?: boolean;
lineWidth?: number;
fill?: any; //boolean or number
fillColor?: any; //null or color/gradient
}
interface linesOptions extends seriesTypeBase {
steps?: boolean;
}
interface barsOptions extends seriesTypeBase {
barWidth?: number;
align?: string;
horizontal?: boolean;
}
interface pointsOptions extends seriesTypeBase {
radius?: number;
symbol?: any;
}
interface gradient {
colors: any[];
}
interface item {
datapoint: number[]; // the point, e.g. [0, 2]
dataIndex: number; // the index of the point in the data array
series: dataSeries; //the series object
seriesIndex: number; //the index of the series
pageX: number;
pageY: number; //the global screen coordinates of the point
}
interface datapoints {
points: number[];
pointsize: number;
format: datapointFormat[];
}
interface datapointFormat {
x?: boolean;
y?: boolean;
number: boolean;
required: boolean;
defaultValue?: number;
}
interface point {
x: number;
y: number;
}
interface offset {
left: number;
top: number;
}
interface canvasPoint {
top: number;
left: number;
bottom?: number;
right?: number;
}
interface axes {
xaxis: axis;
yaxis: axis;
x2axis?: axis;
y2axis?: axis;
}
interface axis extends axisOptions {
options: axisOptions;
p2c(point: point):canvasPoint;
c2p(canvasPoint: canvasPoint):point;
}
interface plugin {
init(options: plotOptions): any;
options?: any;
name?: string;
version?: string;
}
interface plot {
highlight(series: dataSeries, datapoint: item): void;
unhighlight(): void;
unhighlight(series: dataSeries, datapoint: item): void;
setData(data: any): void;
setupGrid(): void;
draw(): void;
triggerRedrawOverlay(): void;
width(): number;
height(): number;
offset(): JQueryCoordinates;
pointOffset(point: point): offset;
resize(): void;
shutdown(): void;
getData(): dataSeries[];
getAxes(): axes;
getXAxes(): axis[];
getYAxes(): axis[];
getPlaceholder(): JQuery;
getCanvas(): HTMLCanvasElement;
getPlotOffset(): canvasPoint;
getOptions(): plotOptions;
}
interface plotStatic {
(placeholder: JQuery, data: dataSeries[], options?: plotOptions): plot;
(placeholder: JQuery, data: any[], options?: plotOptions): plot;
plugins: plugin[];
}
}
interface JQueryStatic {
plot: jquery.flot.plotStatic;
}

View File

@ -0,0 +1,80 @@
function profileLoaded(profileRaw: ProfileRaw[], buildRaw: BuildRaw): void {
$(document.body).empty().append(profileRoot(unraw(profileRaw), unrawBuild(buildRaw)));
}
function unraw(xs: ProfileRaw[]): Profile[] {
const ans = xs.map((x, i) => ({
index: i,
name: x[0],
execution: x[1],
built: x[2],
changed: x[3],
visited: x[4],
depends: x.length > 5 ? x[5] : [],
rdepends: [],
traces: []
} as Profile));
for (const p of ans)
for (const ds of p.depends)
for (const d of ds)
ans[d].rdepends.push(p.index);
return ans;
}
function unrawBuild(b: BuildRaw): Build {
return { dirtyKeys: b.length > 0 ? b[0] : null };
}
function profileRoot(profile: Profile[], build: Build): HTMLElement {
const [s, search] = createSearch(profile);
const t = createTabs(
[ ["Summary", () => reportSummary(profile, build)]
, ["Rules", () => reportRuleTable(profile, search)]
, ["Parallelizability", () => reportParallelism(profile)]
, ["Details", () => reportDetails(profile, search)]
// , ["Why rebuild", () => reportRebuild(profile, search)]
]);
return <table class="fill">
<tr><td style="padding-top: 8px; padding-bottom: 8px;">
<a href="https://shakebuild.com/" style="font-size: 20px; text-decoration: none; color: #3131a7; font-weight: bold;">
Shake profile report
</a>
<span style="color:gray;white-space:pre;"> - generated at {generated} by hls-graph v{version}</span>
</td></tr>
<tr><td>{s}</td></tr>
<tr><td height="100%">{t}</td></tr>
</table>;
}
function createTabs(xs: Array<[string, () => HTMLElement]>): HTMLElement {
const bodies: Array< [HTMLElement, () => void] > = xs.map(x => {
const el = <div style="padding:5px;width:100%;height:100%;min-width:150px;min-height:150px;overflow:auto;display:none;"></div>;
const upd = lazy(() => $(el).append(x[1]()));
return pair(el, upd);
});
let lbls = [];
const f = (i: int) => () => {
bodies[i][1]();
lbls.map((x, j) => $(x).toggleClass("active", i === j));
bodies.map((x, j) => $(x[0]).toggle(i === j));
$(window).trigger("resize");
};
lbls = xs.map((x, i) => <a onclick={f(i)}>{x[0]}</a>);
f(0)();
return <table class="fill">
<tr><td>
<table width="100%" style="border-spacing:0px;"><tr class="tabstrip">
<td width="20" class="bottom">&nbsp;</td>
<td style="padding:0px;">{lbls}</td>
<td width="100%" class="bottom">&nbsp;</td>
</tr></table>
</td></tr>
<tr height="100%">
<td style="background-color:white;">
{bodies.map(fst)}
</td>
</tr>
</table>;
}

View File

@ -0,0 +1,112 @@
function reportCmdPlot(profile: Profile[]): HTMLElement {
// first find the end point
const runs = findRuns(profile);
if (runs.length === 0) {
return <div>
<h2>No data found</h2>
<p>
The Shake database contains no rules which ran traced commands.
</p><p>
You can populate this information by using {varLink("cmd")} or wrapping your <tt>IO</tt> actions in {varLink("traced")}.
</p>
</div>;
}
const combo = <select>
{runs.map(([run, time], i) =>
<option>
{showRun(run) + " (" + showTime(time) + ") "}
{i === 0 ? "" : " - may be incomplete"}
</option>)};
</select>;
const warning = <i></i>;
const plot = <div style="width:100%; height:100%;"></div>;
const plotData: Prop<jquery.flot.dataSeries[]> = new Prop([]);
bindPlot(plot, plotData, {
legend: { show: true, position: "nw", sorted: "reverse" },
series: { stack: true, lines: { fill: 1, lineWidth: 0 } },
yaxis: { min: 0 },
xaxis: { tickFormatter: showTime }
});
function setPlotData(runsIndex: int) {
const [run, end] = runs[runsIndex];
const profileRun = profile.filter(p => p.built === run);
// Make sure we max(0,) every step in the process, in case one does parallelism of threads
const missing = profileRun.map(untraced).sum();
$(warning).text(missing < 1 ? "" : "Warning: " + showTime(missing) + " of execution was not traced.");
const series = calcPlotData(end, profileRun, 100);
const res = [];
for (const s in series)
res.push({label: s, data: series[s].map((x, i) => pair(end * i / 100, x))});
plotData.set(res);
}
setPlotData(0);
$(combo).change(() => setPlotData(combo.selectedIndex));
return <table class="fill">
<tr>
<td width="100%" style="text-align:center;"><h2>Number of commands executing over time</h2></td>
<td>{combo}</td>
</tr>
<tr>
<td height="100%" colspan="2">{plot}</td>
</tr>
<tr>
<td colspan="2" style="text-align:center;">Time since the start of building. {warning}</td>
</tr>
</table>;
}
// Find which runs had traced commands and when the last stopped, sort so most recent first
function findRuns(profile: Profile[]): Array<[timestamp, seconds]> {
const runs: MapInt<seconds> = {};
for (const p of profile) {
if (p.traces.length > 0) {
if (p.traces.length === 1 && p.traces[0].command === "")
continue; // the fake end command
const old = runs[p.built];
const end = p.traces.last().stop;
runs[p.built] = old === undefined ? end : Math.max(old, end);
}
}
const runsList: Array<[timestamp, seconds]> = [];
for (const i in runs)
runsList.push(pair(Number(i), runs[i]));
runsList.sort(compareFst);
return runsList;
}
function calcPlotData(end: seconds, profile: Profile[], buckets: int): MapString<number[]> {
const ans: MapString<number[]> = {};
for (const p of profile) {
for (const t of p.traces) {
let xs: number[];
if (t.command in ans)
xs = ans[t.command];
else {
xs = [];
for (let i = 0; i < buckets; i++)
xs.push(0); // fill with 1 more element, but the last bucket will always be 0
ans[t.command] = xs;
}
const start = t.start * buckets / end;
const stop = t.stop * buckets / end;
if (Math.floor(start) === Math.floor(stop))
xs[Math.floor(start)] += stop - start;
else {
for (let j = Math.ceil(start); j < Math.floor(stop); j++)
xs[j]++;
xs[Math.floor(start)] += Math.ceil(start) - start;
xs[Math.floor(stop)] += stop - Math.floor(stop);
}
}
}
return ans;
}

View File

@ -0,0 +1,34 @@
function reportCmdTable(profile: Profile[], search: Prop<Search>): HTMLElement {
const columns: Column[] =
[ {field: "name", label: "Name", width: 200}
, {field: "count", label: "Count", width: 65, alignRight: true, show: showInt}
, {field: "total", label: "Total", width: 75, alignRight: true, show: showTime}
, {field: "average", label: "Average", width: 75, alignRight: true, show: showTime}
, {field: "max", label: "Max", width: 75, alignRight: true, show: showTime}
];
return newTable(columns, search.map(cmdData), "total", true);
}
function cmdData(search: Search): object[] {
const res: MapString< {count: int, total: seconds, max: seconds} > = {};
search.forEachProfile(p => {
for (const t of p.traces) {
const time = t.stop - t.start;
if (t.command === "")
continue; // do nothing
else if (!(t.command in res))
res[t.command] = {count: 1, total: time, max: time};
else {
const ans = res[t.command];
ans.count++;
ans.total += time;
ans.max = Math.max(ans.max, time);
}
}
});
const res2 = [];
for (const i in res)
res2.push({name: i, average: res[i].total / res[i].count, ...res[i]});
return res2;
}

View File

@ -0,0 +1,33 @@
function reportDetails(profile: Profile[], search: Prop<Search>): HTMLElement {
const result = <div class="details"></div>;
const self: Prop<pindex> = new Prop(0);
search.event(xs => self.set(xs.mapProfile((p, _) => p.index).maximum()));
const f = (i: pindex) => <a onclick={() => self.set(i)}>{profile[i].name}</a>;
self.event(i => {
const p = profile[i];
const content = <ul>
<li><b>Name:</b> {p.name}</li>
<li><b>Built:</b> {showRun(p.built)}</li>
<li><b>Changed:</b> {showRun(p.changed)}</li>
<li><b>Execution time:</b>{showTime(p.execution)}</li>
<li><b>Traced commands:</b>
<ol>
{p.traces.map(t => <li>{t.command} took {showTime(t.stop - t.start)}</li>)}
</ol>
</li>
<li><b>Dependencies:</b>
<ol>
{p.depends.map(ds => <li><ul>{ds.map(d => <li>{f(d)}</li>)}</ul></li>)}
</ol>
</li>
<li><b>Things that depend on me:</b>
<ul>
{p.rdepends.map(d => <li>{f(d)}</li>)}
</ul>
</li>
</ul>;
$(result).empty().append(content);
});
return result;
}

View File

@ -0,0 +1,74 @@
function reportParallelism(profile: Profile[]): HTMLElement {
// now simulate for -j1 .. -j24
const plotData: jquery.flot.dataSeries[] =
[ {label: "Realistic (based on current dependencies)", data: [], color: "#3131a7"}
, {label: "Ideal (if no dependencies and perfect speedup)", data: [], color: "green"}
, {label: "Gap", data: [], color: "orange"}
];
let threads1: seconds;
for (let threads = 1; threads <= 24; threads++) {
const taken = simulateThreads(profile, threads)[0];
if (threads === 1) threads1 = taken;
plotData[0].data.push([threads, taken]);
plotData[1].data.push([threads, threads1 / threads]);
plotData[2].data.push([threads, Math.max(0, taken - (threads1 / threads))]);
}
const plot = <div style="width:100%; height:100%;"></div>;
bindPlot(plot, new Prop(plotData), {
xaxis: { tickDecimals: 0 },
yaxis: { min: 0, tickFormatter: showTime }
});
return <table class="fill">
<tr>
<td style="text-align:center;"><h2>Time to build at different number of threads</h2></td>
</tr>
<tr>
<td height="100%">{plot}</td>
</tr>
<tr>
<td style="text-align:center;">Number of threads available.</td>
</tr>
</table>;
}
// Simulate running N threads over the profile, return:
// [total time take, point at which each entry kicked off]
function simulateThreads(profile: Profile[], threads: int): [seconds, seconds[]] {
// How far are we through this simulation
let timestamp: seconds = 0;
// Who is currently running, with the highest seconds FIRST
const running: Array<[pindex, seconds]> = [];
const started: seconds[] = [];
// Things that are done
const ready: Profile[] = profile.filter(x => x.depends.length === 0);
const waiting: int[] = profile.map(x => x.depends.concatLength()) ; // number I am waiting on before I am done
function runningWait(): void {
const [ind, time] = running.pop();
timestamp = time;
for (const d of profile[ind].rdepends) {
waiting[d]--;
if (waiting[d] === 0)
ready.push(profile[d]);
}
}
while (true) {
// Queue up as many people as we can
while (running.length < threads && ready.length > 0) {
const p = ready.pop();
started[p.index] = timestamp;
running.insertSorted([p.index, timestamp + p.execution], compareSndRev);
}
if (running.length === 0) {
if (waiting.maximum(0) > 0)
throw new Error("Failed to run all tasks");
return [timestamp, started];
}
runningWait();
}
}

View File

@ -0,0 +1,30 @@
function reportRebuild(profile: Profile[], search: Prop<Search>): HTMLElement {
const depth: int[] = [];
for (const p of profile) {
depth[p.index] = p.depends.flat().map(d => depth[d] + 1).maximum(0);
}
const ind: pindex = search.get().mapProfile((p, _) => p.index).sortOn(i => -depth[i])[0];
const p = profile[ind];
function f(p: Profile): HTMLElement[] {
const res = [];
while (p.depends.length !== 0) {
const ds = p.depends.flat().sortOn(i => -depth[i]);
res.push(<li><select style="width:400px;">{ds.slice(0, 1).map(x => <option>{profile[x].name}</option>)}</select></li>);
p = profile[ds[0]];
}
return res;
}
return <div>
<h2>Why did it rebuild?</h2>
<p>
Rule {p.name + " " + (p.built === 0 ? "rebuild in the last run" : "did not rebuild")}
</p>
<ul>
{f(p)}
</ul>
</div>;
}

View File

@ -0,0 +1,61 @@
function reportRuleTable(profile: Profile[], search: Prop<Search>): HTMLElement {
const [etimes, wtimes] = calcEWTimes(profile, 24);
const columns: Column[] =
[ {field: "name", label: "Name", width: 400}
, {field: "count", label: "Count", width: 65, alignRight: true, show: showInt}
, {field: "leaf", label: "Leaf", width: 60, alignRight: true}
, {field: "visited", label: "Visit", width: 50, alignRight: true}
, {field: "run", label: "Run", width: 50, alignRight: true}
, {field: "changed", label: "Change", width: 60, alignRight: true}
, {field: "time", label: "Time", width: 75, alignRight: true, show: showTime}
, {field: "etime", label: "ETime", width: 75, alignRight: true, show: showTime}
, {field: "wtime", label: "WTime", width: 75, alignRight: true, show: showTime}
];
return newTable(columns, search.map(s => ruleData(etimes, wtimes, s)), "time", true);
}
// Calculate the exclusive time of each rule at some number of threads
function calcEWTimes(profile: Profile[], threads: int): [seconds[], seconds[]] {
const [_, started] = simulateThreads(profile, threads);
const starts = started.map((s, i) => pair(i, s)).sort(compareSnd);
const costs = starts.map(([ind, start], i) => {
// find out who else runs before I finish
const execution = profile[ind].execution;
const end = start + execution;
let overlap = 0; // how much time I am overlapped for
let exclusive = 0; // how much time I am the only runner
let finisher = start; // the first overlapping person to finish
for (let j = i + 1; j < starts.length; j++) {
const [jInd, jStarts] = starts[j];
if (jStarts > end) break;
overlap += Math.min(end - jStarts, profile[jInd].execution);
exclusive += Math.max(0, Math.min(jStarts, end) - finisher);
finisher = Math.max(finisher, jStarts + profile[jInd].execution);
}
exclusive += Math.max(0, end - finisher);
return triple(ind, execution === 0 ? 0 : execution * (execution / (execution + overlap)), exclusive);
});
const etimes: seconds[] = [];
const wtimes: seconds[] = [];
for (const [ind, etime, wtime] of costs) {
etimes[ind] = etime;
wtimes[ind] = wtime;
}
return [etimes, wtimes];
}
function ruleData(etimes: seconds[], wtimes: seconds[], search: Search): object[] {
return search.mapProfiles((ps, name) => ({
name,
count: ps.length,
leaf: ps.every(p => p.depends.length === 0),
run: ps.map(p => p.built).minimum(),
visited: ps.map(p => p.visited).minimum(),
changed: ps.some(p => p.built === p.changed),
time: ps.map(p => p.execution).sum(),
etime: ps.map(p => etimes[p.index]).sum(),
wtime: ps.map(p => wtimes[p.index]).sum(),
}));
}

View File

@ -0,0 +1,155 @@
function reportSummary(profile: Profile[], build: Build): HTMLElement {
let countLast: int = 0; // number of rules run in the last run
let visitedLast: int = 0; // number of rules visited in the last run
let highestRun: timestamp = 0; // highest run you have seen (add 1 to get the count of runs)
let sumExecution: seconds = 0; // build time in total
let sumExecutionLast: seconds = 0; // build time in total
let countTrace: int = -1; let countTraceLast: int = -1; // traced commands run
// start both are -1 because the end command will have run in the previous step
let maxTraceStopLast: seconds = 0; // time the last traced command stopped
for (const p of profile) {
sumExecution += p.execution;
highestRun = Math.max(highestRun, p.changed); // changed is always greater or equal to built
countTrace += p.traces.length;
if (p.built === 0) {
sumExecutionLast += p.execution;
countLast++;
countTraceLast += p.traces.length;
if (p.traces.length > 0)
maxTraceStopLast = Math.max(maxTraceStopLast, p.traces.last().stop);
}
if (p.visited === 0) {
visitedLast++;
}
}
return <div>
<h2>Totals</h2>
<ul>
<li><b>Runs:</b> {showInt(highestRun + 1)} <span class="note">total number of runs so far.</span></li>
<li><b>Rules:</b> {showInt(profile.length)} ({showInt(countLast)} in last run) <span class="note">number of defined build rules.</span></li>
</ul>
<h2>Performance</h2>
<ul>
<li><b>Build time:</b> {showTime(sumExecution)} <span class="note">how long a complete build would take single threaded.</span></li>
<li><b>Last build time:</b> {showTime(maxTraceStopLast)} <span class="note">how long the last build take.</span></li>
<li><b>Parallelism:</b> {(maxTraceStopLast === 0 ? 0 : sumExecutionLast / maxTraceStopLast).toFixed(2)} <span class="note">average number of commands executing simultaneously in the last build.</span></li>
<li><b>Speculative critical path:</b> {showTime(speculativeCriticalPath(profile))} <span class="note">how long it would take on infinite CPUs.</span></li>
<li><b>Precise critical path:</b> {showTime(preciseCriticalPath(profile))} <span class="note">critical path not speculatively executing.</span></li>
</ul>
<h2>This run</h2>
<ul>
<li><b>Rules built:</b> {showInt(countLast)} <span class="note">Total number of rules built in this run</span></li>
<li><b>Rules visited:</b> {showInt(visitedLast - countLast)} <span class="note">Total number of rules looked up from the values store in this run</span></li>
<li><b>Dirty set:</b>{renderDirtySet(build,profile)}</li>
</ul>
</div>;
}
function renderDirtySet(build: Build, profile: Profile[]) {
if(build.dirtyKeys === null) {
return "ALL";
}
else {
return <ul>
{build.dirtyKeys.map( d => {return <li>{profile[d].name}</li>})
}
</ul>;
}
}
function speculativeCriticalPath(profile: Profile[]): seconds {
const criticalPath: seconds[] = []; // the critical path to any element
let maxCriticalPath: seconds = 0;
for (const p of profile) {
let cost = 0;
for (const ds of p.depends)
for (const d of ds)
cost = Math.max(cost, criticalPath[d]);
cost += p.execution;
maxCriticalPath = Math.max(cost, maxCriticalPath);
criticalPath[p.index] = cost;
}
return maxCriticalPath;
}
/*
Calculating a precise critical path, taking into account the deep dependeny structure, is non-obvious.
Dependencies have the type [{X}], e.g:
X = [{a,b},{c,d}]
That is r builds a and b, then after those both complete (assuming they don't change), it builds c and d,
then it is finished. Importantly, r doesn't start building c/d until after a and b have finished. This
detail extends the critical path.
To calculate the precise critical path, we simulate with the notion of demand and waiting.
*/
function preciseCriticalPath(profile: Profile[]): seconds {
const waiting: int[] = profile.map(x => x.depends.concatLength()) ; // number I am waiting on before I am done
const demanded: boolean[] = []; // I have been demanded by someone
const oncomplete: Array<() => void> = []; // Completion functions
const complete: boolean[] = []; // Who is complete already
const running: Array<[pindex, seconds]> = [];
let timestamp: seconds = 0;
// demand dependency set N of a rule
function demandN(p: Profile, round: int): void {
for (; round < p.depends.length; round++) {
let todo = p.depends[round].length; // Number before we continue
const step = () => {
todo--;
if (todo === 0)
demandN(p, round + 1);
};
for (const d of p.depends[round]) {
if (complete[d])
todo--;
else {
const old = oncomplete[d];
oncomplete[d] = !old ? step : () => { old(); step(); };
demand(profile[d]);
}
}
if (todo !== 0) break;
// todo === 0, so continue (equivalent to calling step but tail recursive)
}
}
// demand a particular rule
function demand(p: Profile): void {
if (demanded[p.index]) return;
demanded[p.index] = true;
if (waiting[p.index] === 0)
running.insertSorted([p.index, timestamp + p.execution], compareSndRev);
else
demandN(p, 0);
}
// We don't know the targets we ask for, so we approximate by saying the ones which nothing depends on
for (const p of profile) {
if (p.rdepends.length === 0)
demand(p);
}
while (running.length > 0) {
const [ind, time] = running.pop();
timestamp = time;
complete[ind] = true;
if (oncomplete[ind]) {
oncomplete[ind]();
delete oncomplete[ind];
}
for (const d of profile[ind].rdepends) {
waiting[d]--;
if (waiting[d] === 0 && demanded[d])
running.insertSorted([d, timestamp + profile[d].execution], compareSndRev);
}
}
for (let i = 0; i < profile.length; i++)
if (!complete[i])
throw new Error("Failed to run all tasks");
return timestamp;
}

View File

@ -0,0 +1,139 @@
// A mapping from names (rule names or those matched from rule parts)
// to the indicies in profiles.
class Search {
private profile: Profile[];
private mapping: MapString<int[]>;
constructor(profile: Profile[], mapping?: MapString<int[]>) {
this.profile = profile;
if (mapping !== undefined)
this.mapping = mapping;
else {
this.mapping = {};
for (const p of profile)
this.mapping[p.name] = [p.index];
}
}
public forEachProfiles(f: (ps: Profile[], group: string) => void): void {
for (const s in this.mapping)
f(this.mapping[s].map(i => this.profile[i]), s);
}
public forEachProfile(f: (p: Profile, group: string) => void): void {
this.forEachProfiles((ps, group) => ps.forEach(p => f(p, group)));
}
public mapProfiles<A>(f: (ps: Profile[], group: string) => A): A[] {
const res: A[] = [];
this.forEachProfiles((ps, group) => res.push(f(ps, group)));
return res;
}
public mapProfile<A>(f: (p: Profile, group: string) => A): A[] {
const res: A[] = [];
this.forEachProfile((p, group) => res.push(f(p, group)));
return res;
}
}
function createSearch(profile: Profile[]): [HTMLElement, Prop<Search>] {
const caption = <div>Found {profile.length} entries, not filtered or grouped.</div>;
const input = <input id="search" type="text" value="" placeholder="Filter and group"
style="width: 100%; font-size: 16px; border-radius: 8px; padding: 5px 10px; border: 2px solid #999;" />;
const res = new Prop(new Search(profile));
$(input).on("change keyup paste", () => {
const s: string = $(input).val();
if (s === "") {
res.set(new Search(profile));
$(caption).text("Found " + profile.length + " entries, not filtered or grouped.");
} else if (s.indexOf("(") === -1) {
const mapping = {};
let found = 0 ;
for (const p of profile) {
if (p.name.indexOf(s) !== -1) {
found++;
mapping[p.name] = [p.index];
}
}
res.set(new Search(profile, mapping));
$(caption).text("Substring filtered to " + found + " / " + profile.length + " entries, not grouped.");
} else {
let f;
try {
f = new Function("return " + s);
} catch (e) {
$(caption).text("Error compiling function, " + e);
return;
}
const mapping = {};
let groups = 0;
let found = 0;
environmentAll = profile;
for (const p of profile) {
environmentThis = p;
environmentGroup = [];
let bool: boolean;
try {
bool = f();
} catch (e) {
$(caption).text("Error running function, " + e);
return;
}
if (bool) {
found++;
const name = environmentGroup.length === 0 ? p.name : environmentGroup.join(" ");
if (name in mapping)
mapping[name].push(p.index);
else {
groups++;
mapping[name] = [p.index];
}
}
}
res.set(new Search(profile, mapping));
$(caption).text("Function filtered to " + found + " / " + profile.length + " entries, " +
(groups === found ? "not grouped." : groups + " groups."));
}
});
const body =
<table width="100%" style="padding-bottom: 17px;">
<tr>
<td width="100%">{input}</td>
<td style="padding-left:6px;padding-right: 6px;">{searchHelp(input)}</td>
</tr>
<tr>
<td>{caption}</td>
</tr>
</table>;
return [body, res];
}
function searchHelp(input: HTMLElement): HTMLElement {
const examples: Array<[string, string]> =
[ ["Only the last run", "run(0)"]
, ["Only the last visited", "visited(0)"]
, ["Named 'Main'", "named(\"Main\")"]
, ["Group by file extension", "named(/(\\.[_0-9a-z]+)$/)"]
, ["No dependencies (an input)", "leaf()"]
, ["Didn't change when it last rebuilt", "unchanged()"]
, ["Ran 'gcc'", "command(\"gcc\")"]
];
const f = (code: string) => () => {
$(input).val((i, x) => x + (x === "" ? "" : " && ") + code);
$(input).trigger("change");
};
const dropdown = <div class="dropdown" style="display:none;">
<ul style="padding-left:30px;">
{examples.map(([desc, code]) => <li><a onclick={f(code)}><tt>{code}</tt></a> <span class="note">{desc}</span></li>)}
</ul>
</div>;
const arrow_down = <span style="vertical-align:middle;font-size:80%;">&#9660;</span>;
const arrow_up = <span style="vertical-align:middle;font-size:80%;display:none;">&#9650;</span>;
const show_inner = () => { $(dropdown).toggle(); $(arrow_up).toggle(); $(arrow_down).toggle(); };
return <div>
<button style="white-space:nowrap;padding-top:5px;padding-bottom:5px;" onclick={show_inner}>
<b style="font-size:150%;vertical-align:middle;">+</b>&nbsp; Filter and Group &nbsp;
{arrow_down}{arrow_up}
</button>{dropdown}
</div>;
}

View File

@ -0,0 +1,28 @@
/* tslint:disable */
"use strict";
function initProgress() {
$(function () {
$(".version").html("Generated by <a href='https://shakebuild.com'>Shake " + version + "</a>.");
$("#output").html("");
for (const x of progress) {
var actual: [number, number][] = [];
var ideal: [number, number][] = [];
// Start at t = 5 seconds, since the early progress jumps a lot
for (var t = 5; t < x.values.length; t++) {
var y = x.values[t];
actual.push([y.idealSecs, y.actualSecs]);
ideal.push([y.idealSecs, y.idealSecs]);
}
var ys = [{ data: ideal, color: "gray" }, { label: x.name, data: actual, color: "red" }];
var div = $("<div class='plot'>");
$("#output").append(div);
$.plot(div, ys, {
xaxis: {
transform: function (v) { return -v; },
inverseTransform: function (v) { return -v; }
}
});
}
})
}

View File

@ -0,0 +1,9 @@
{
"compilerOptions": {
"target": "esnext",
"outFile": "../shake.js",
"newLine": "lf",
"jsx": "react",
"alwaysStrict": true
}
}

View File

@ -0,0 +1,19 @@
{
"defaultSeverity": "error",
"extends": [
"tslint:recommended"
],
"rules": {
"max-line-length": false,
"no-consecutive-blank-lines": [true, 2],
"variable-name": false,
"curly": false,
"trailing-comma": [true, {"multiline": "never", "singleline": "never"}],
"interface-name": false,
"interface-over-type-literal": false,
"no-shadowed-variable": false,
"arrow-parens": [true, "ban-single-arg-parens"],
"object-literal-sort-keys": [false],
"forin": false
}
}

View File

@ -0,0 +1,94 @@
// Stuff that Shake generates and injects in
// The version of Shake
declare const version: string;
declare const generated: string;
/////////////////////////////////////////////////////////////////////
// PROFILE DATA
type timestamp = int;
interface Trace {
command: string;
start: seconds;
stop: seconds;
}
type pindex = int; // an index into the list of profiles
interface Profile {
index: pindex; // My index in the list of profiles
name: string; // Name of the thing I built
execution: seconds; // Seconds I took to execute
built: timestamp; // Timestamp at which I was recomputed
visited: timestamp; // Timestamp at which I was last visited
changed: timestamp; // Timestamp at which I last changed
depends: pindex[][]; // What I depend on (always lower than my index)
rdepends: pindex[]; // What depends on me
traces: Trace[]; // List of traces
}
function untraced(p: Profile): seconds {
return Math.max(0, p.execution - p.traces.map(t => t.stop - t.start).sum());
}
interface Build {
dirtyKeys: pindex[];
}
type TraceRaw =
[ string
, seconds
, seconds
];
type ProfileRaw =
[ string
, seconds
, timestamp
, timestamp
, timestamp
, pindex[][] // Optional
, TraceRaw[] // Optional
];
type BuildRaw =
[ pindex[] // Optional
];
/////////////////////////////////////////////////////////////////////
// PROGRESS DATA
declare const progress: Array<{name: string, values: Progress[]}>;
interface Progress {
idealSecs: number;
idealPerc: number;
actualSecs: number;
actualPerc: number;
}
/////////////////////////////////////////////////////////////////////
// BASIC UI TOOLKIT
class Prop<A> {
private val: A;
private callback: ((val: A) => void);
constructor(val: A) { this.val = val; this.callback = () => { return; }; }
public get(): A { return this.val; }
public set(val: A): void {
this.val = val;
this.callback(val);
}
public event(next: (val: A) => void): void {
const old = this.callback;
this.callback = val => { old(val); next(val); };
next(this.val);
}
public map<B>(f: (val: A) => B): Prop<B> {
const res = new Prop(f(this.get()));
this.event(a => res.set(f(a)));
return res;
}
}

235
hls-graph/html/ts/util.ts Normal file
View File

@ -0,0 +1,235 @@
type key = string | number;
type seconds = number;
type color = string;
type MapString<T> = { [key: string]: T };
type MapNumber<T> = { [key: number]: T };
type int = number;
type MapInt<T> = MapNumber<T>;
/////////////////////////////////////////////////////////////////////
// JQUERY EXTENSIONS
// tslint:disable-next-line: interface-name
interface JQuery {
enable(x: boolean): JQuery;
}
jQuery.fn.enable = function(x: boolean) {
// Set the values to enabled/disabled
return this.each(function() {
if (x)
$(this).removeAttr("disabled");
else
$(this).attr("disabled", "disabled");
});
};
/////////////////////////////////////////////////////////////////////
// BROWSER HELPER METHODS
// Given "?foo=bar&baz=1" returns {foo:"bar",baz:"1"}
function uriQueryParameters(s: string): MapString<string> {
// From https://stackoverflow.com/questions/901115/get-querystring-values-with-jquery/3867610#3867610
const params: MapString<string> = {};
const a = /\+/g; // Regex for replacing addition symbol with a space
const r = /([^&=]+)=?([^&]*)/g;
const d = (x: string) => decodeURIComponent(x.replace(a, " "));
const q = s.substring(1);
while (true) {
const e = r.exec(q);
if (!e) break;
params[d(e[1])] = d(e[2]);
}
return params;
}
/////////////////////////////////////////////////////////////////////
// STRING FORMATTING
function showTime(x: seconds): string {
function digits(x: seconds) {const s = String(x); return s.length === 1 ? "0" + s : s; }
if (x >= 3600) {
x = Math.round(x / 60);
return Math.floor(x / 60) + "h" + digits(x % 60) + "m";
} else if (x >= 60) {
x = Math.round(x);
return Math.floor(x / 60) + "m" + digits(x % 60) + "s";
} else
return x.toFixed(2) + "s";
}
function showPerc(x: number): string {
return (x * 100).toFixed(2) + "%";
}
function showInt(x: int): string {
// From https://stackoverflow.com/questions/2901102/how-to-print-a-number-with-commas-as-thousands-separators-in-javascript
// Show, with commas
return x.toString().replace(/\B(?=(\d{3})+(?!\d))/g, ",");
}
function showRun(run: timestamp): string {
return run === 0 ? "Latest run" : run + " run" + plural(run) + " ago";
}
function plural(n: int, not1 = "s", is1 = ""): string {
return n === 1 ? is1 : not1;
}
/////////////////////////////////////////////////////////////////////
// MISC
function compareFst<A>(a: [number, A], b: [number, A]): number {
return a[0] - b[0];
}
function compareSnd<A>(a: [A, number], b: [A, number]): number {
return a[1] - b[1];
}
function compareSndRev<A>(a: [A, number], b: [A, number]): number {
return b[1] - a[1];
}
function pair<A, B>(a: A, b: B): [A, B] {
return [a, b];
}
function triple<A, B, C>(a: A, b: B, c: C): [A, B, C] {
return [a, b, c];
}
function fst<A, B>([x, _]: [A, B]): A {
return x;
}
function snd<A, B>([_, x]: [A, B]): B {
return x;
}
function execRegExp(r: string | RegExp, s: string): string[] {
if (typeof r === "string")
return s.indexOf(r) === -1 ? null : [];
else
return r.exec(s);
}
function cache<K, V>(key: (k: K) => string, op: (k: K) => V): (k: K) => V {
const store: MapString<V> = {};
return k => {
const s = key(k);
if (!(s in store))
store[s] = op(k);
return store[s];
};
}
function lazy<V>(thunk: () => V): () => V {
let store: V = null;
let done = false;
return () => {
if (!done) {
store = thunk();
done = true;
}
return store;
};
}
interface Array<T> {
insertSorted(x: T, compare: (a: T, b: T) => number): T[];
concatLength<A, T extends A[]>(): int;
sortOn(f: (x: T) => number): T[];
last(): T;
sum<T extends number>(): number;
maximum<T extends number>(def?: number): number;
minimum<T extends number>(def?: number): number;
}
Array.prototype.sum = function<T>(this: number[]): number {
let res = 0;
for (const x of this)
res += x;
return res;
};
Array.prototype.insertSorted = function<T>(this: T[], x: T, compare: (a: T, b: T) => number): T[] {
let start = 0;
let stop = this.length - 1;
let middle = 0;
while (start <= stop) {
middle = Math.floor((start + stop) / 2);
if (compare(this[middle], x) > 0)
stop = middle - 1;
else
start = middle + 1;
}
this.splice(start, 0, x);
return this;
};
Array.prototype.concatLength = function<A>(this: A[][]): int {
let res = 0;
for (const x of this)
res += x.length;
return res;
};
Array.prototype.sortOn = function<T>(this: T[], f: (x: T) => number): T[] {
return this.map(x => pair(f(x), x)).sort(compareFst).map(snd);
};
Array.prototype.last = function<T>(this: T[]): T {
return this[this.length - 1];
};
Array.prototype.maximum = function<T>(this: number[], def?: number): number {
if (this.length === 0) return def;
let res: number = this[0];
for (let i = 1; i < this.length; i++)
res = Math.max(res, this[i]);
return res;
};
Array.prototype.minimum = function<T>(this: number[], def?: number): number {
if (this.length === 0) return def;
let res: number = this[0];
for (let i = 1; i < this.length; i++)
res = Math.min(res, this[i]);
return res;
};
// Use JSX with el instead of React.createElement
// Originally from https://gist.github.com/sergiodxa/a493c98b7884128081bb9a281952ef33
// our element factory
function createElement(type: string, props?: MapString<any>, ...children: any[]) {
const element = document.createElement(type);
for (const name in props || {}) {
if (name.substr(0, 2) === "on")
element.addEventListener(name.substr(2), props[name]);
else
element.setAttribute(name, props[name]);
}
for (const child of children.flat(10)) {
const c = typeof child === "object" ? child : document.createTextNode(child.toString());
element.appendChild(c);
}
return element;
}
// How .tsx gets desugared
const React = {createElement};

View File

@ -4,22 +4,23 @@ module Development.IDE.Graph(
shakeOptions,
Rules,
Action, action,
actionFinally, actionBracket, actionCatch,
Shake.ShakeException(..),
Key(..),
actionFinally, actionBracket, actionCatch, actionFork,
-- * Configuration
ShakeOptions(shakeAllowRedefineRules, shakeThreads, shakeFiles, shakeExtra),
getShakeExtra, getShakeExtraRules, newShakeExtra,
-- * Explicit parallelism
parallel,
-- * Oracle rules
Shake.ShakeValue, Shake.RuleResult,
ShakeValue, RuleResult,
-- * Special rules
alwaysRerun,
-- * Batching
reschedule,
) where
import Development.IDE.Graph.Database
import Development.IDE.Graph.Internal.Action
import Development.IDE.Graph.Internal.Options
import Development.IDE.Graph.Internal.Rules
import qualified Development.Shake as Shake
import Development.IDE.Graph.Internal.Types

View File

@ -1,6 +1,8 @@
module Development.IDE.Graph.Classes(
Show(..), Typeable, Eq(..), Hashable(..), Binary(..), NFData(..)
Show(..), Typeable, Eq(..), Hashable(..), NFData(..)
) where
import Development.Shake.Classes
import Control.DeepSeq
import Data.Hashable
import Data.Typeable

View File

@ -1,36 +1,58 @@
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE ExistentialQuantification #-}
module Development.IDE.Graph.Database(
Shake.ShakeDatabase,
SomeShakeValue(..),
ShakeDatabase,
ShakeValue,
shakeOpenDatabase,
shakeRunDatabase,
shakeRunDatabaseForKeys,
Shake.shakeProfileDatabase,
shakeProfileDatabase,
) where
import Data.Typeable
import Data.Dynamic
import Data.Maybe
import Development.IDE.Graph.Classes ()
import Development.IDE.Graph.Internal.Action
import Development.IDE.Graph.Internal.Database
import Development.IDE.Graph.Internal.Options
import Development.IDE.Graph.Internal.Profile (writeProfile)
import Development.IDE.Graph.Internal.Rules
import Development.Shake (ShakeValue)
import Development.Shake.Classes
import qualified Development.Shake.Database as Shake
import Development.IDE.Graph.Internal.Types
shakeOpenDatabase :: ShakeOptions -> Rules () -> IO (IO Shake.ShakeDatabase, IO ())
shakeOpenDatabase a b = Shake.shakeOpenDatabase (fromShakeOptions a) (fromRules b)
data ShakeDatabase = ShakeDatabase !Int [Action ()] Database
data SomeShakeValue = forall k . ShakeValue k => SomeShakeValue k
instance Eq SomeShakeValue where SomeShakeValue a == SomeShakeValue b = cast a == Just b
instance Hashable SomeShakeValue where hashWithSalt s (SomeShakeValue x) = hashWithSalt s x
instance Show SomeShakeValue where show (SomeShakeValue x) = show x
-- Placeholder to be the 'extra' if the user doesn't set it
data NonExportedType = NonExportedType
shakeOpenDatabase :: ShakeOptions -> Rules () -> IO (IO ShakeDatabase, IO ())
shakeOpenDatabase opts rules = pure (shakeNewDatabase opts rules, pure ())
shakeNewDatabase :: ShakeOptions -> Rules () -> IO ShakeDatabase
shakeNewDatabase opts rules = do
let extra = fromMaybe (toDyn NonExportedType) $ shakeExtra opts
(theRules, actions) <- runRules extra rules
db <- newDatabase extra theRules
pure $ ShakeDatabase (length actions) actions db
shakeRunDatabase :: ShakeDatabase -> [Action a] -> IO ([a], [IO ()])
shakeRunDatabase = shakeRunDatabaseForKeys Nothing
-- Only valid if we never pull on the results, which we don't
unvoid :: Functor m => m () -> m a
unvoid = fmap undefined
shakeRunDatabaseForKeys
:: Maybe [SomeShakeValue]
:: Maybe [Key]
-- ^ Set of keys changed since last run. 'Nothing' means everything has changed
-> Shake.ShakeDatabase
-> ShakeDatabase
-> [Action a]
-> IO ([a], [IO ()])
shakeRunDatabaseForKeys _keys a b =
-- Shake upstream does not accept the set of keys changed yet
-- https://github.com/ndmitchell/shake/pull/802
Shake.shakeRunDatabase a (map fromAction b)
shakeRunDatabaseForKeys keysChanged (ShakeDatabase lenAs1 as1 db) as2 = do
incDatabase db keysChanged
as <- fmap (drop lenAs1) $ runActions db $ map unvoid as1 ++ as2
return (as, [])
-- | Given a 'ShakeDatabase', write an HTML profile to the given file about the latest run.
shakeProfileDatabase :: ShakeDatabase -> FilePath -> IO ()
shakeProfileDatabase (ShakeDatabase _ _ s) file = writeProfile file s

View File

@ -1,38 +1,127 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ConstraintKinds #-}
module Development.IDE.Graph.Internal.Action where
module Development.IDE.Graph.Internal.Action
( ShakeValue
, actionFork
, actionBracket
, actionCatch
, actionFinally
, alwaysRerun
, apply1
, apply
, parallel
, reschedule
, runActions
) where
import Control.Concurrent.Async
import Control.Exception
import Control.Monad.Fail
import Control.Monad.Extra
import Control.Monad.IO.Class
import qualified Development.Shake as Shake
import Development.Shake.Classes
import qualified Development.Shake.Rule as Shake
import Control.Monad.Trans.Class
import Control.Monad.Trans.Reader
import Data.IORef
import Development.IDE.Graph.Classes
import Development.IDE.Graph.Internal.Database
import Development.IDE.Graph.Internal.Types
import System.Exit
import Development.IDE.Graph.Internal.Rules (RuleResult)
newtype Action a = Action {fromAction :: Shake.Action a}
deriving (Monad, Applicative, Functor, MonadIO, MonadFail)
type ShakeValue a = (Show a, Typeable a, Eq a, Hashable a, NFData a)
alwaysRerun :: Action ()
alwaysRerun = Action Shake.alwaysRerun
alwaysRerun = do
ref <- Action $ asks actionDeps
liftIO $ writeIORef ref Nothing
-- No-op for now
reschedule :: Double -> Action ()
reschedule = Action . Shake.reschedule
reschedule _ = pure ()
parallel :: [Action a] -> Action [a]
parallel = Action . Shake.parallel . map fromAction
parallel [] = pure []
parallel [x] = fmap (:[]) x
parallel xs = do
a <- Action ask
deps <- liftIO $ readIORef $ actionDeps a
case deps of
Nothing ->
-- if we are already in the rerun mode, nothing we do is going to impact our state
liftIO $ mapConcurrently (ignoreState a) xs
Just deps -> do
(newDeps, res) <- liftIO $ unzip <$> mapConcurrently (usingState a) xs
liftIO $ writeIORef (actionDeps a) $ (deps ++) <$> concatMapM id newDeps
pure res
where
usingState a x = do
ref <- newIORef $ Just []
res <- runReaderT (fromAction x) a{actionDeps=ref}
deps <- readIORef ref
pure (deps, res)
ignoreState :: SAction -> Action b -> IO b
ignoreState a x = do
ref <- newIORef Nothing
runReaderT (fromAction x) a{actionDeps=ref}
actionFork :: Action a -> (Async a -> Action b) -> Action b
actionFork act k = do
a <- Action ask
deps <- liftIO $ readIORef $ actionDeps a
let db = actionDatabase a
case deps of
Nothing -> do
-- if we are already in the rerun mode, nothing we do is going to impact our state
[res] <- liftIO $ withAsync (ignoreState a act) $ \as -> runActions db [k as]
return res
_ ->
error "please help me"
isAsyncException :: SomeException -> Bool
isAsyncException e
| Just (_ :: AsyncCancelled) <- fromException e = True
| Just (_ :: AsyncException) <- fromException e = True
| Just (_ :: ExitCode) <- fromException e = True
| otherwise = False
actionCatch :: Exception e => Action a -> (e -> Action a) -> Action a
actionCatch a b = Action $ Shake.actionCatch (fromAction a) (fromAction . b)
actionCatch a b = do
v <- Action ask
Action $ lift $ catchJust f (runReaderT (fromAction a) v) (\x -> runReaderT (fromAction (b x)) v)
where
-- Catch only catches exceptions that were caused by this code, not those that
-- are a result of program termination
f e | isAsyncException e = Nothing
| otherwise = fromException e
actionBracket :: IO a -> (a -> IO b) -> (a -> Action c) -> Action c
actionBracket a b c = Action $ Shake.actionBracket a b (fromAction . c)
actionBracket a b c = do
v <- Action ask
Action $ lift $ bracket a b (\x -> runReaderT (fromAction (c x)) v)
actionFinally :: Action a -> IO b -> Action a
actionFinally a b = Action $ Shake.actionFinally (fromAction a) b
actionFinally a b = do
v <- Action ask
Action $ lift $ finally (runReaderT (fromAction a) v) b
apply1 :: (Shake.RuleResult key ~ value, Shake.ShakeValue key, Typeable value) => key -> Action value
apply1 = Action . Shake.apply1
apply1 :: (RuleResult key ~ value, ShakeValue key, Typeable value) => key -> Action value
apply1 k = head <$> apply [k]
apply :: (Shake.RuleResult key ~ value, Shake.ShakeValue key, Typeable value) => [key] -> Action [value]
apply = Action . Shake.apply
apply :: (RuleResult key ~ value, ShakeValue key, Typeable value) => [key] -> Action [value]
apply ks = do
db <- Action $ asks actionDatabase
(is, vs) <- liftIO $ build db ks
ref <- Action $ asks actionDeps
deps <- liftIO $ readIORef ref
whenJust deps $ \deps ->
liftIO $ writeIORef ref $ Just $ is ++ deps
pure vs
runActions :: Database -> [Action a] -> IO [a]
runActions db xs = do
deps <- newIORef Nothing
runReaderT (fromAction $ parallel xs) $ SAction db deps

View File

@ -0,0 +1,285 @@
-- We deliberately want to ensure the function we add to the rule database
-- has the constraints we need on it when we get it out.
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
module Development.IDE.Graph.Internal.Database (newDatabase, incDatabase, build) where
import Control.Concurrent.Async
import Control.Concurrent.Extra
import Control.Exception
import Control.Monad
import Control.Monad.IO.Class (MonadIO (liftIO))
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Reader
import qualified Control.Monad.Trans.State.Strict as State
import Data.Dynamic
import Data.Either
import Data.Foldable (traverse_)
import Data.IORef.Extra
import Data.IntSet (IntSet)
import qualified Data.IntSet as Set
import Data.Maybe
import Data.Tuple.Extra
import Development.IDE.Graph.Classes
import qualified Development.IDE.Graph.Internal.Ids as Ids
import Development.IDE.Graph.Internal.Intern
import qualified Development.IDE.Graph.Internal.Intern as Intern
import Development.IDE.Graph.Internal.Rules
import Development.IDE.Graph.Internal.Types
import System.IO.Unsafe
import System.Time.Extra (duration)
newDatabase :: Dynamic -> TheRules -> IO Database
newDatabase databaseExtra databaseRules = do
databaseStep <- newIORef $ Step 0
databaseLock <- newLock
databaseIds <- newIORef Intern.empty
databaseValues <- Ids.empty
databaseReverseDeps <- Ids.empty
databaseReverseDepsLock <- newLock
databaseDirtySet <- newIORef Nothing
pure Database{..}
-- | Increment the step and mark dirty
incDatabase :: Database -> Maybe [Key] -> IO ()
-- all keys are dirty
incDatabase db Nothing = do
modifyIORef' (databaseStep db) $ \(Step i) -> Step $ i + 1
writeIORef (databaseDirtySet db) Nothing
withLock (databaseLock db) $
Ids.forMutate (databaseValues db) $ \_ -> second $ \case
Clean x -> Dirty (Just x)
Dirty x -> Dirty x
Running _ _ x -> Dirty x
-- only some keys are dirty
incDatabase db (Just kk) = do
modifyIORef' (databaseStep db) $ \(Step i) -> Step $ i + 1
intern <- readIORef (databaseIds db)
let dirtyIds = mapMaybe (`Intern.lookup` intern) kk
transitiveDirtyIds <- transitiveDirtySet db dirtyIds
writeIORef (databaseDirtySet db) (Just $ Set.toList transitiveDirtyIds)
withLock (databaseLock db) $
Ids.forMutate (databaseValues db) $ \i -> \case
(k, Running _ _ x) -> (k, Dirty x)
(k, Clean x) | i `Set.member` transitiveDirtyIds ->
(k, Dirty (Just x))
other -> other
-- | Unwrap and build a list of keys in parallel
build
:: forall key value . (RuleResult key ~ value, Typeable key, Show key, Hashable key, Eq key, Typeable value)
=> Database -> [key] -> IO ([Id], [value])
build db keys = do
(ids, vs) <- runAIO $ fmap unzip $ either return liftIO =<< builder db (map (Right . Key) keys)
pure (ids, map (asV . resultValue) vs)
where
asV :: Value -> value
asV (Value x) = unwrapDynamic x
-- | Build a list of keys and return their results.
-- If none of the keys are dirty, we can return the results immediately.
-- Otherwise, a blocking computation is returned *which must be evaluated asynchronously* to avoid deadlock.
builder
:: Database -> [Either Id Key] -> AIO (Either [(Id, Result)] (IO [(Id, Result)]))
builder db@Database{..} keys = do
-- Things that I need to force before my results are ready
toForce <- liftIO $ newIORef []
results <- withLockAIO databaseLock $ do
flip traverse keys $ \idKey -> do
-- Resolve the id
id <- case idKey of
Left id -> pure id
Right key -> liftIO $ do
ids <- readIORef databaseIds
case Intern.lookup key ids of
Just v -> pure v
Nothing -> do
(ids, id) <- pure $ Intern.add key ids
writeIORef' databaseIds ids
return id
-- Spawn the id if needed
status <- liftIO $ Ids.lookup databaseValues id
val <- case fromMaybe (fromRight undefined idKey, Dirty Nothing) status of
(_, Clean r) -> pure r
(_, Running force val _) -> do
liftIO $ modifyIORef toForce (Wait force :)
pure val
(key, Dirty s) -> do
act <- unliftAIO (refresh db key id s)
let (force, val) = splitIO (join act)
liftIO $ Ids.insert databaseValues id (key, Running force val s)
liftIO $ modifyIORef toForce (Spawn force:)
pure val
pure (id, val)
toForceList <- liftIO $ readIORef toForce
waitAll <- unliftAIO $ mapConcurrentlyAIO_ id toForceList
case toForceList of
[] -> return $ Left results
_ -> return $ Right $ do
waitAll
pure results
-- | Refresh a key:
-- * If no dirty dependencies and we have evaluated the key previously, then we refresh it in the current thread.
-- This assumes that the implementation will be a lookup
-- * Otherwise, we spawn a new thread to refresh the dirty deps (if any) and the key itself
refresh :: Database -> Key -> Id -> Maybe Result -> AIO (IO Result)
refresh db key id result@(Just me@Result{resultDeps=Just deps}) = do
res <- builder db $ map Left deps
case res of
Left res ->
if isDirty res
then asyncWithCleanUp $ liftIO $ compute db key id RunDependenciesChanged result
else pure $ compute db key id RunDependenciesSame result
Right iores -> asyncWithCleanUp $ liftIO $ do
res <- iores
let mode = if isDirty res then RunDependenciesChanged else RunDependenciesSame
compute db key id mode result
where
isDirty = any (\(_,dep) -> resultBuilt me < resultChanged dep)
refresh db key id result =
asyncWithCleanUp $ liftIO $ compute db key id RunDependenciesChanged result
-- | Compute a key.
compute :: Database -> Key -> Id -> RunMode -> Maybe Result -> IO Result
compute db@Database{..} key id mode result = do
let act = runRule databaseRules key (fmap resultData result) mode
deps <- newIORef $ Just []
(execution, RunResult{..}) <-
duration $ runReaderT (fromAction act) $ SAction db deps
built <- readIORef databaseStep
deps <- readIORef deps
let changed = if runChanged == ChangedRecomputeDiff then built else maybe built resultChanged result
built' = if runChanged /= ChangedNothing then built else changed
-- only update the deps when the rule ran with changes
actualDeps = if runChanged /= ChangedNothing then deps else previousDeps
previousDeps= resultDeps =<< result
let res = Result runValue built' changed built actualDeps execution runStore
case actualDeps of
Just deps | not(null deps) &&
runChanged /= ChangedNothing
-> do
void $ forkIO $
updateReverseDeps id db (fromMaybe [] previousDeps) (Set.fromList deps)
_ -> pure ()
withLock databaseLock $
Ids.insert databaseValues id (key, Clean res)
pure res
--------------------------------------------------------------------------------
-- Lazy IO trick
data Box a = Box {fromBox :: a}
-- | Split an IO computation into an unsafe lazy value and a forcing computation
splitIO :: IO a -> (IO (), a)
splitIO act = do
let act2 = Box <$> act
let res = unsafePerformIO act2
(void $ evaluate res, fromBox res)
--------------------------------------------------------------------------------
-- Reverse dependencies
-- | Update the reverse dependencies of an Id
updateReverseDeps
:: Id -- ^ Id
-> Database
-> [Id] -- ^ Previous direct dependencies of Id
-> IntSet -- ^ Current direct dependencies of Id
-> IO ()
updateReverseDeps myId db prev new = withLock (databaseReverseDepsLock db) $ uninterruptibleMask_ $ do
forM_ prev $ \d ->
unless (d `Set.member` new) $
doOne (Set.delete myId) d
forM_ (Set.elems new) $
doOne (Set.insert myId)
where
doOne f id = do
rdeps <- getReverseDependencies db id
Ids.insert (databaseReverseDeps db) id (f $ fromMaybe mempty rdeps)
getReverseDependencies :: Database -> Id -> IO (Maybe (IntSet))
getReverseDependencies db = Ids.lookup (databaseReverseDeps db)
transitiveDirtySet :: Foldable t => Database -> t Id -> IO IntSet
transitiveDirtySet database = flip State.execStateT Set.empty . traverse_ loop
where
loop x = do
seen <- State.get
if x `Set.member` seen then pure () else do
State.put (Set.insert x seen)
next <- lift $ getReverseDependencies database x
traverse_ loop (maybe mempty Set.toList next)
-- | IO extended to track created asyncs to clean them up when the thread is killed,
-- generalizing 'withAsync'
newtype AIO a = AIO { unAIO :: ReaderT (IORef [Async ()]) IO a }
deriving newtype (Applicative, Functor, Monad, MonadIO)
runAIO :: AIO a -> IO a
runAIO (AIO act) = do
asyncs <- newIORef []
runReaderT act asyncs `onException` cleanupAsync asyncs
asyncWithCleanUp :: AIO a -> AIO (IO a)
asyncWithCleanUp act = do
st <- AIO ask
io <- unliftAIO act
liftIO $ uninterruptibleMask $ \restore -> do
a <- async $ restore io
atomicModifyIORef'_ st (void a :)
return $ wait a
withLockAIO :: Lock -> AIO a -> AIO a
withLockAIO lock act = do
io <- unliftAIO act
liftIO $ withLock lock io
unliftAIO :: AIO a -> AIO (IO a)
unliftAIO act = do
st <- AIO ask
return $ runReaderT (unAIO act) st
cleanupAsync :: IORef [Async a] -> IO ()
cleanupAsync ref = uninterruptibleMask_ $ do
asyncs <- readIORef ref
mapM_ (\a -> throwTo (asyncThreadId a) AsyncCancelled) asyncs
mapM_ waitCatch asyncs
data Wait a
= Wait {justWait :: !a}
| Spawn {justWait :: !a}
deriving Functor
waitOrSpawn :: Wait (IO a) -> IO (Either (IO a) (Async a))
waitOrSpawn (Wait io) = pure $ Left io
waitOrSpawn (Spawn io) = Right <$> async io
mapConcurrentlyAIO_ :: (a -> IO ()) -> [Wait a] -> AIO ()
mapConcurrentlyAIO_ _ [] = pure ()
mapConcurrentlyAIO_ f [one] = liftIO $ justWait $ fmap f one
mapConcurrentlyAIO_ f many = do
ref <- AIO ask
waits <- liftIO $ uninterruptibleMask $ \restore -> do
waits <- liftIO $ traverse waitOrSpawn (map (fmap (restore . f)) many)
let asyncs = rights waits
liftIO $ atomicModifyIORef'_ ref (asyncs ++)
return waits
liftIO $ traverse_ (either id wait) waits

View File

@ -0,0 +1,160 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE UnboxedTuples #-}
-- Note that argument order is more like IORef than Map, because its mutable
module Development.IDE.Graph.Internal.Ids(
Ids, Id,
empty, insert, lookup, fromList,
null, size, sizeUpperBound,
forWithKeyM_, forCopy, forMutate,
toList, elems, toMap
) where
import Control.Exception
import Control.Monad.Extra
import Data.Functor
import qualified Data.HashMap.Strict as Map
import Data.IORef.Extra
import Data.List.Extra (zipFrom)
import Data.Maybe
import Data.Primitive.Array hiding (fromList)
import Development.IDE.Graph.Internal.Intern (Id)
import GHC.Exts (RealWorld)
import GHC.IO (IO (..))
import Prelude hiding (lookup, null)
newtype Ids a = Ids (IORef (S a))
data S a = S
{capacity :: {-# UNPACK #-} !Int -- ^ Number of entries in values, initially 0
,used :: {-# UNPACK #-} !Int -- ^ Capacity that has been used, assuming no gaps from index 0, initially 0
,values :: {-# UNPACK #-} !(MutableArray RealWorld (Maybe a))
}
empty :: IO (Ids a)
empty = do
let capacity = 0
let used = 0
values <- newArray capacity Nothing
Ids <$> newIORef S{..}
fromList :: [a] -> IO (Ids a)
fromList xs = do
let capacity = length xs
let used = capacity
values <- newArray capacity Nothing
forM_ (zipFrom 0 xs) $ \(i, x) ->
writeArray values i $ Just x
Ids <$> newIORef S{..}
sizeUpperBound :: Ids a -> IO Int
sizeUpperBound (Ids ref) = do
S{..} <- readIORef ref
pure used
size :: Ids a -> IO Int
size (Ids ref) = do
S{..} <- readIORef ref
let go !acc i
| i < 0 = pure acc
| otherwise = do
v <- readArray values i
if isJust v then go (acc+1) (i-1) else go acc (i-1)
go 0 (used-1)
toMap :: Ids a -> IO (Map.HashMap Id a)
toMap ids = do
mp <- Map.fromList <$> toListUnsafe ids
pure $! mp
forWithKeyM_ :: Ids a -> (Id -> a -> IO ()) -> IO ()
forWithKeyM_ (Ids ref) f = do
S{..} <- readIORef ref
let go !i | i >= used = pure ()
| otherwise = do
v <- readArray values i
whenJust v $ f $ fromIntegral i
go $ i+1
go 0
forCopy :: Ids a -> (a -> b) -> IO (Ids b)
forCopy (Ids ref) f = do
S{..} <- readIORef ref
values2 <- newArray capacity Nothing
let go !i | i >= used = pure ()
| otherwise = do
v <- readArray values i
whenJust v $ \v -> writeArray values2 i $ Just $ f v
go $ i+1
go 0
Ids <$> newIORef (S capacity used values2)
forMutate :: Ids a -> (Id -> a -> a) -> IO ()
forMutate (Ids ref) f = do
S{..} <- readIORef ref
let go !i | i >= used = pure ()
| otherwise = do
v <- readArray values i
whenJust v $ \v -> writeArray values i $! Just $! f i v
go $ i+1
go 0
toListUnsafe :: Ids a -> IO [(Id, a)]
toListUnsafe (Ids ref) = do
S{..} <- readIORef ref
-- execute in O(1) stack
-- see https://neilmitchell.blogspot.co.uk/2015/09/making-sequencemapm-for-io-take-o1-stack.html
let index _ i | i >= used = []
index r i | IO io <- readArray values i = case io r of
(# r, Nothing #) -> index r (i+1)
(# r, Just v #) -> (fromIntegral i, v) : index r (i+1)
IO $ \r -> (# r, index r 0 #)
toList :: Ids a -> IO [(Id, a)]
toList ids = do
xs <- toListUnsafe ids
let demand (_:xs) = demand xs
demand [] = ()
evaluate $ demand xs
pure xs
elems :: Ids a -> IO [a]
elems ids = map snd <$> toList ids
null :: Ids a -> IO Bool
null ids = (== 0) <$> sizeUpperBound ids
insert :: Ids a -> Id -> a -> IO ()
insert (Ids ref) (i) v = do
S{..} <- readIORef ref
let ii = fromIntegral i
if ii < capacity then do
writeArray values ii $ Just v
when (ii >= used) $ writeIORef' ref S{used=ii+1,..}
else do
c2<- pure $ max (capacity * 2) (ii + 10000)
v2 <- newArray c2 Nothing
copyMutableArray v2 0 values 0 capacity
writeArray v2 ii $ Just v
writeIORef' ref $ S c2 (ii+1) v2
lookup :: Ids a -> Id -> IO (Maybe a)
lookup (Ids ref) (i) = do
S{..} <- readIORef ref
let ii = fromIntegral i
if ii < used then
readArray values ii
else
pure Nothing

View File

@ -0,0 +1,41 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Development.IDE.Graph.Internal.Intern(
Intern, Id,
empty, insert, add, lookup, toList, fromList
) where
import qualified Data.HashMap.Strict as Map
import Data.List (foldl')
import Development.IDE.Graph.Classes
import Prelude hiding (lookup)
-- Invariant: The first field is the highest value in the Map
data Intern a = Intern {-# UNPACK #-} !Int !(Map.HashMap a Id)
type Id = Int
empty :: Intern a
empty = Intern 0 Map.empty
insert :: (Eq a, Hashable a) => a -> Id -> Intern a -> Intern a
insert k v (Intern n mp) = Intern (max n v) $ Map.insert k v mp
add :: (Eq a, Hashable a) => a -> Intern a -> (Intern a, Id)
add k (Intern v mp) = (Intern v2 $ Map.insert k v2 mp, v2)
where v2 = v + 1
lookup :: (Eq a, Hashable a) => a -> Intern a -> Maybe Id
lookup k (Intern _ mp) = Map.lookup k mp
toList :: Intern a -> [(a, Id)]
toList (Intern _ mp) = Map.toList mp
fromList :: (Eq a, Hashable a) => [(a, Id)] -> Intern a
fromList xs = Intern (foldl' max 0 [i | (_, i) <- xs]) (Map.fromList xs)

View File

@ -2,13 +2,12 @@
module Development.IDE.Graph.Internal.Options where
import Control.Monad.Trans.Reader
import Data.Dynamic
import qualified Data.HashMap.Strict as Map
import Development.IDE.Graph.Internal.Action
import Development.IDE.Graph.Internal.Rules
import qualified Development.Shake as Shake
import Development.IDE.Graph.Internal.Types
data ShakeOptions = ShakeOptions {
-- | Has no effect, kept only for api compatibility with Shake
shakeThreads :: Int,
shakeFiles :: FilePath,
shakeExtra :: Maybe Dynamic,
@ -19,22 +18,15 @@ data ShakeOptions = ShakeOptions {
shakeOptions :: ShakeOptions
shakeOptions = ShakeOptions 0 ".shake" Nothing False False
fromShakeOptions :: ShakeOptions -> Shake.ShakeOptions
fromShakeOptions ShakeOptions{..} = Shake.shakeOptions{
Shake.shakeThreads = shakeThreads,
Shake.shakeFiles = shakeFiles,
Shake.shakeExtra = maybe Map.empty f shakeExtra,
Shake.shakeAllowRedefineRules = shakeAllowRedefineRules,
Shake.shakeTimings = shakeTimings
}
where f x = Map.singleton (dynTypeRep x) x
getShakeExtra :: Typeable a => Action (Maybe a)
getShakeExtra = Action Shake.getShakeExtra
getShakeExtra = do
extra <- Action $ asks $ databaseExtra . actionDatabase
pure $ fromDynamic extra
getShakeExtraRules :: Typeable a => Rules (Maybe a)
getShakeExtraRules = Rules Shake.getShakeExtraRules
getShakeExtraRules = do
extra <- Rules $ asks rulesExtra
pure $ fromDynamic extra
newShakeExtra :: Typeable a => a -> Maybe Dynamic
newShakeExtra = Just . toDyn

View File

@ -0,0 +1,71 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}
module Development.IDE.Graph.Internal.Paths (getDataFile) where
import Paths_hls_graph
#ifndef FILE_EMBED
import Control.Exception (SomeException (SomeException), catch)
import Control.Monad (filterM)
import System.Directory (doesFileExist, getCurrentDirectory)
import System.Environment (getExecutablePath)
import System.FilePath (takeDirectory, (</>))
import System.IO.Unsafe (unsafePerformIO)
#endif
#ifdef FILE_EMBED
import qualified Data.ByteString as BS
import qualified Data.ByteString as LBS
import Data.FileEmbed
initDataDirectory :: IO ()
initDataDirectory = pure ()
htmlDataFiles :: [(FilePath, BS.ByteString)]
htmlDataFiles =
[ ("profile.html", $(embedFile "html/profile.html"))
, ("progress.html", $(embedFile "html/progress.html"))
, ("shake.js", $(embedFile "html/shake.js"))
]
readDataFileHTML :: FilePath -> IO LBS.ByteString
readDataFileHTML file = do
case lookup file htmlDataFiles of
Nothing -> fail $ "Could not find data file " ++ file ++ " in embedded data files!"
Just x -> pure (LBS.fromStrict x)
manualDirData :: [(FilePath, BS.ByteString)]
manualDirData = $(embedDir "docs/manual")
hasManualData :: IO Bool
hasManualData = pure True
copyManualData :: FilePath -> IO ()
copyManualData dest = do
createDirectoryRecursive dest
forM_ manualDirData $ \(file, bs) -> do
BS.writeFile (dest </> file) bs
#else
-- We want getDataFileName to be relative to the current directory on program startup,
-- even if we issue a change directory command. Therefore, first call caches, future ones read.
{-# NOINLINE dataDirs #-}
dataDirs :: [String]
dataDirs = unsafePerformIO $ do
datdir <- getDataDir
exedir <- takeDirectory <$> getExecutablePath `catch` \SomeException{} -> pure ""
curdir <- getCurrentDirectory
pure $ [datdir] ++ [exedir | exedir /= ""] ++ [curdir]
getDataFile :: FilePath -> IO FilePath
getDataFile file = do
let poss = map (</> file) dataDirs
res <- filterM doesFileExist poss
case res of
[] -> fail $ unlines $ ("Could not find data file " ++ file ++ ", looked in:") : map (" " ++) poss
x:_ -> pure x
#endif

View File

@ -0,0 +1,221 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}
{- HLINT ignore "Redundant bracket" -} -- a result of CPP expansion
module Development.IDE.Graph.Internal.Profile (writeProfile) where
import Data.Bifunctor
import qualified Data.ByteString.Lazy.Char8 as LBS
import Data.Char
import Data.Dynamic (toDyn)
import qualified Data.HashMap.Strict as Map
import Data.IORef
import Data.IntMap (IntMap)
import qualified Data.IntMap as IntMap
import Data.List (dropWhileEnd, foldl',
intercalate, partition,
sort, sortBy)
import Data.List.Extra (nubOrd)
import Data.Maybe
import Data.Time (defaultTimeLocale,
formatTime,
getCurrentTime,
iso8601DateFormat)
import Development.IDE.Graph.Classes
import qualified Development.IDE.Graph.Internal.Ids as Ids
import Development.IDE.Graph.Internal.Paths
import Development.IDE.Graph.Internal.Types
import qualified Language.Javascript.DGTable as DGTable
import qualified Language.Javascript.Flot as Flot
import qualified Language.Javascript.JQuery as JQuery
import Numeric.Extra (showDP)
import System.FilePath
import System.IO.Unsafe (unsafePerformIO)
import System.Time.Extra (Seconds)
#ifdef FILE_EMBED
import Data.FileEmbed
import Language.Haskell.TH.Syntax (runIO)
#endif
-- | Generates an report given some build system profiling data.
writeProfile :: FilePath -> Database -> IO ()
writeProfile out db = do
dirtyKeys <- readIORef (databaseDirtySet db)
(report, mapping) <- toReport db
let dirtyKeysMapped = mapMaybe (`IntMap.lookup` mapping) <$> dirtyKeys
rpt <- generateHTML (sort <$> dirtyKeysMapped) report
LBS.writeFile out rpt
data ProfileEntry = ProfileEntry
{prfName :: !String, prfBuilt :: !Int, prfChanged :: !Int, prfVisited :: !Int, prfDepends :: [[Int]], prfExecution :: !Seconds}
-- | Eliminate all errors from the database, pretending they don't exist
-- resultsOnly :: Map.HashMap Id (Key, Status) -> Map.HashMap Id (Key, Result (Either BS.ByteString Value))
resultsOnly :: [(Ids.Id, (k, Status))] -> Map.HashMap Ids.Id (k, Result)
resultsOnly mp = Map.map (fmap (\r ->
r{resultDeps = fmap (filter (isJust . flip Map.lookup keep)) $ resultDeps r}
)) keep
where
keep = Map.fromList $ mapMaybe ((traverse.traverse) getResult) mp
-- | Given a map of representing a dependency order (with a show for error messages), find an ordering for the items such
-- that no item points to an item before itself.
-- Raise an error if you end up with a cycle.
dependencyOrder :: (Eq a, Hashable a) => (a -> String) -> [(a,[a])] -> [a]
-- Algorithm:
-- Divide everyone up into those who have no dependencies [Id]
-- And those who depend on a particular Id, Dep :-> Maybe [(Key,[Dep])]
-- Where d :-> Just (k, ds), k depends on firstly d, then remaining on ds
-- For each with no dependencies, add to list, then take its dep hole and
-- promote them either to Nothing (if ds == []) or into a new slot.
-- k :-> Nothing means the key has already been freed
dependencyOrder shw status =
f (map fst noDeps) $
Map.map Just $
Map.fromListWith (++)
[(d, [(k,ds)]) | (k,d:ds) <- hasDeps]
where
(noDeps, hasDeps) = partition (null . snd) status
f [] mp | null bad = []
| otherwise = error $ unlines $
"Internal invariant broken, database seems to be cyclic" :
map (" " ++) bad ++
["... plus " ++ show (length badOverflow) ++ " more ..." | not $ null badOverflow]
where (bad,badOverflow) = splitAt 10 [shw i | (i, Just _) <- Map.toList mp]
f (x:xs) mp = x : f (now++xs) later
where Just free = Map.lookupDefault (Just []) x mp
(now,later) = foldl' g ([], Map.insert x Nothing mp) free
g (free, mp) (k, []) = (k:free, mp)
g (free, mp) (k, d:ds) = case Map.lookupDefault (Just []) d mp of
Nothing -> g (free, mp) (k, ds)
Just todo -> (free, Map.insert d (Just $ (k,ds) : todo) mp)
prepareForDependencyOrder :: Database -> IO (Map.HashMap Ids.Id (Key, Result))
prepareForDependencyOrder db = do
current <- readIORef $ databaseStep db
Map.insert (-1) (Key "alwaysRerun", alwaysRerunResult current) . resultsOnly
<$> Ids.toList (databaseValues db)
-- | Returns a list of profile entries, and a mapping linking a non-error Id to its profile entry
toReport :: Database -> IO ([ProfileEntry], IntMap Int)
toReport db = do
status <- prepareForDependencyOrder db
let order = let shw i = maybe "<unknown>" (show . fst) $ Map.lookup i status
in dependencyOrder shw
$ map (second (fromMaybe [-1] . resultDeps . snd))
$ Map.toList status
ids = IntMap.fromList $ zip order [0..]
steps = let xs = nubOrd $ concat [[resultChanged, resultBuilt, resultVisited] | (_k, Result{..}) <- Map.elems status]
in Map.fromList $ zip (sortBy (flip compare) xs) [0..]
f (k, Result{..}) = ProfileEntry
{prfName = show k
,prfBuilt = fromStep resultBuilt
,prfVisited = fromStep resultVisited
,prfChanged = fromStep resultChanged
,prfDepends = map pure $ mapMaybe (`IntMap.lookup` ids) $ fromMaybe [-1] $ resultDeps
,prfExecution = resultExecution
}
where fromStep i = fromJust $ Map.lookup i steps
pure ([maybe (error "toReport") f $ Map.lookup i status | i <- order], ids)
alwaysRerunResult :: Step -> Result
alwaysRerunResult current = Result (Value $ toDyn "<alwaysRerun>") (Step 0) (Step 0) current (Just []) 0 mempty
readDataFileHTML :: FilePath -> IO LBS.ByteString
readDataFileHTML file = LBS.readFile =<< getDataFile ("html" </> file)
generateHTML :: Maybe [Int] -> [ProfileEntry] -> IO LBS.ByteString
generateHTML dirtyKeys xs = do
report <- readDataFileHTML "profile.html"
let f "data/profile-data.js" = pure $ LBS.pack $ "var profile =\n" ++ generateJSONProfile xs
f "data/build-data.js" = pure $ LBS.pack $ "var build =\n" ++ generateJSONBuild dirtyKeys
f other = error other
runTemplate f report
generateJSONBuild :: Maybe [Ids.Id] -> String
generateJSONBuild (Just dirtyKeys) = jsonList [jsonList (map show dirtyKeys)]
generateJSONBuild Nothing = jsonList []
generateJSONProfile :: [ProfileEntry] -> String
generateJSONProfile = jsonListLines . map showEntry
where
showEntry ProfileEntry{..} = jsonList $
[show prfName
,showTime prfExecution
,show prfBuilt
,show prfChanged
,show prfVisited
] ++
[show prfDepends | not (null prfDepends)]
showTime x = if '.' `elem` y then dropWhileEnd (== '.') $ dropWhileEnd (== '0') y else y
where y = showDP 4 x
jsonListLines :: [String] -> String
jsonListLines xs = "[" ++ intercalate "\n," xs ++ "\n]"
jsonList :: [String] -> String
jsonList xs = "[" ++ intercalate "," xs ++ "]"
-- Very hard to abstract over TH, so we do it with CPP
#ifdef FILE_EMBED
#define FILE(x) (pure (LBS.fromStrict $(embedFile =<< runIO (x))))
#else
#define FILE(x) (LBS.readFile =<< (x))
#endif
libraries :: [(String, IO LBS.ByteString)]
libraries =
[("jquery.js", FILE(JQuery.file))
,("jquery.dgtable.js", FILE(DGTable.file))
,("jquery.flot.js", FILE(Flot.file Flot.Flot))
,("jquery.flot.stack.js", FILE(Flot.file Flot.FlotStack))
]
-- | Template Engine. Perform the following replacements on a line basis:
--
-- * <script src="foo"></script> ==> <script>[[foo]]</script>
--
-- * <link href="foo" rel="stylesheet" type="text/css" /> ==> <style type="text/css">[[foo]]</style>
runTemplate :: (FilePath -> IO LBS.ByteString) -> LBS.ByteString -> IO LBS.ByteString
runTemplate ask = lbsMapLinesIO f
where
link = LBS.pack "<link href=\""
script = LBS.pack "<script src=\""
f x | Just file <- LBS.stripPrefix script y = do res <- grab file; pure $ LBS.pack "<script>\n" `LBS.append` res `LBS.append` LBS.pack "\n</script>"
| Just file <- LBS.stripPrefix link y = do res <- grab file; pure $ LBS.pack "<style type=\"text/css\">\n" `LBS.append` res `LBS.append` LBS.pack "\n</style>"
| otherwise = pure x
where
y = LBS.dropWhile isSpace x
grab = asker . takeWhile (/= '\"') . LBS.unpack
asker o@(splitFileName -> ("lib/",x)) =
case lookup x libraries of
Nothing -> error $ "Template library, unknown library: " ++ o
Just act -> act
asker "shake.js" = readDataFileHTML "shake.js"
asker "data/metadata.js" = do
time <- getCurrentTime
pure $ LBS.pack $
"var version = \"0\"" ++
"\nvar generated = " ++ show (formatTime defaultTimeLocale (iso8601DateFormat (Just "%H:%M:%S")) time)
asker x = ask x
-- Perform a mapM on each line and put the result back together again
lbsMapLinesIO :: (LBS.ByteString -> IO LBS.ByteString) -> LBS.ByteString -> IO LBS.ByteString
-- If we do the obvious @fmap LBS.unlines . mapM f@ then all the monadic actions are run on all the lines
-- before it starts producing the lazy result, killing streaming and having more stack usage.
-- The real solution (albeit with too many dependencies for something small) is a streaming library,
-- but a little bit of unsafePerformIO does the trick too.
lbsMapLinesIO f = pure . LBS.unlines . map (unsafePerformIO . f) . LBS.lines

View File

@ -1,24 +1,60 @@
-- We deliberately want to ensure the function we add to the rule database
-- has the constraints we need on it when we get it out.
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RecordWildCards #-}
module Development.IDE.Graph.Internal.Rules where
import Control.Monad.Fail
import Control.Monad.IO.Class
import qualified Data.ByteString as BS
import Development.IDE.Graph.Internal.Action
import qualified Development.Shake as Shake
import Development.Shake.Classes
import qualified Development.Shake.Rule as Shake
import Development.IDE.Graph.Classes
import Control.Exception.Extra
import Control.Monad
import Control.Monad.IO.Class
import qualified Data.ByteString as BS
import Data.Dynamic
import Data.Typeable
import Data.IORef
import qualified Data.HashMap.Strict as Map
import Control.Monad.Trans.Reader
import Development.IDE.Graph.Internal.Types
import Data.Maybe
newtype Rules a = Rules {fromRules :: Shake.Rules a}
deriving (Monoid, Semigroup, Monad, Applicative, Functor, MonadIO, MonadFail)
-- | The type mapping between the @key@ or a rule and the resulting @value@.
-- See 'addBuiltinRule' and 'Development.Shake.Rule.apply'.
type family RuleResult key -- = value
action :: Action a -> Rules ()
action = Rules . Shake.action . fromAction
action x = do
ref <- Rules $ asks rulesActions
liftIO $ modifyIORef' ref (void x:)
addRule
:: (Shake.RuleResult key ~ value, Shake.ShakeValue key, Typeable value, NFData value, Show value)
=> (key -> Maybe BS.ByteString -> Shake.RunMode -> Action (Shake.RunResult value))
:: forall key value .
(RuleResult key ~ value, Typeable key, Hashable key, Eq key, Typeable value)
=> (key -> Maybe BS.ByteString -> RunMode -> Action (RunResult value))
-> Rules ()
addRule f = Rules $ Shake.addBuiltinRule Shake.noLint Shake.noIdentity $ \k bs r -> fromAction $ f k bs r
addRule f = do
ref <- Rules $ asks rulesMap
liftIO $ modifyIORef' ref $ Map.insert (typeRep (Proxy :: Proxy key)) (toDyn f2)
where
f2 :: Key -> Maybe BS.ByteString -> RunMode -> Action (RunResult Value)
f2 (Key a) b c = do
v <- f (fromJust $ cast a :: key) b c
v <- liftIO $ evaluate v
pure $ (Value . toDyn) <$> v
runRule
:: TheRules -> Key -> Maybe BS.ByteString -> RunMode -> Action (RunResult Value)
runRule rules key@(Key t) bs mode = case Map.lookup (typeOf t) rules of
Nothing -> liftIO $ errorIO "Could not find key"
Just x -> unwrapDynamic x key bs mode
runRules :: Dynamic -> Rules () -> IO (TheRules, [Action ()])
runRules rulesExtra (Rules rules) = do
rulesActions <- newIORef []
rulesMap <- newIORef Map.empty
runReaderT rules SRules{..}
(,) <$> readIORef rulesMap <*> readIORef rulesActions

View File

@ -0,0 +1,154 @@
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Development.IDE.Graph.Internal.Types where
import Control.Applicative
import Control.Concurrent.Extra
import Control.Monad.Catch
import Control.Monad.Fail
import Control.Monad.IO.Class
import Control.Monad.Trans.Reader
import qualified Data.ByteString as BS
import Data.Dynamic
import qualified Data.HashMap.Strict as Map
import Data.IORef
import Data.IntSet (IntSet)
import Data.Maybe
import Data.Typeable
import Development.IDE.Graph.Classes
import Development.IDE.Graph.Internal.Ids
import Development.IDE.Graph.Internal.Intern
import System.Time.Extra (Seconds)
unwrapDynamic :: forall a . Typeable a => Dynamic -> a
unwrapDynamic x = fromMaybe (error msg) $ fromDynamic x
where msg = "unwrapDynamic failed: Expected " ++ show (typeRep (Proxy :: Proxy a)) ++
", but got " ++ show (dynTypeRep x)
---------------------------------------------------------------------
-- RULES
type TheRules = Map.HashMap TypeRep Dynamic
newtype Rules a = Rules (ReaderT SRules IO a)
deriving (Monad, Applicative, Functor, MonadIO, MonadFail)
data SRules = SRules {
rulesExtra :: !Dynamic,
rulesActions :: !(IORef [Action ()]),
rulesMap :: !(IORef TheRules)
}
---------------------------------------------------------------------
-- ACTIONS
newtype Action a = Action {fromAction :: ReaderT SAction IO a}
deriving (Monad, Applicative, Functor, MonadIO, MonadFail, MonadThrow, MonadCatch, MonadMask)
data SAction = SAction {
actionDatabase :: !Database,
actionDeps :: !(IORef (Maybe [Id])) -- Nothing means always rerun
}
---------------------------------------------------------------------
-- DATABASE
newtype Step = Step Int
deriving (Eq,Ord,Hashable)
data Key = forall a . (Typeable a, Eq a, Hashable a, Show a) => Key a
instance Eq Key where
Key a == Key b = Just a == cast b
instance Hashable Key where
hashWithSalt i (Key x) = hashWithSalt i (typeOf x, x)
instance Show Key where
show (Key x) = show x
newtype Value = Value Dynamic
data Database = Database {
databaseExtra :: Dynamic,
databaseRules :: TheRules,
databaseStep :: !(IORef Step),
databaseDirtySet :: IORef (Maybe [Id]),
-- Hold the lock while mutating Ids/Values
databaseLock :: !Lock,
databaseIds :: !(IORef (Intern Key)),
databaseValues :: !(Ids (Key, Status)),
databaseReverseDeps :: !(Ids IntSet),
databaseReverseDepsLock :: !Lock
}
data Status
= Clean Result
| Dirty (Maybe Result)
| Running (IO ()) Result (Maybe Result)
getResult :: Status -> Maybe Result
getResult (Clean re) = Just re
getResult (Dirty m_re) = m_re
getResult (Running _ _ m_re) = m_re
data Result = Result {
resultValue :: !Value,
resultBuilt :: !Step, -- ^ the step when it was last recomputed
resultChanged :: !Step, -- ^ the step when it last changed
resultVisited :: !Step, -- ^ the step when it was last looked up
resultDeps :: !(Maybe [Id]), -- ^ Nothing = alwaysRerun
resultExecution :: !Seconds, -- ^ How long it took, last time it ran
resultData :: BS.ByteString
}
---------------------------------------------------------------------
-- Running builds
-- | What mode a rule is running in, passed as an argument to 'BuiltinRun'.
data RunMode
= RunDependenciesSame -- ^ My dependencies have not changed.
| RunDependenciesChanged -- ^ At least one of my dependencies from last time have changed, or I have no recorded dependencies.
deriving (Eq,Show)
instance NFData RunMode where rnf x = x `seq` ()
-- | How the output of a rule has changed.
data RunChanged
= ChangedNothing -- ^ Nothing has changed.
| ChangedStore -- ^ The stored value has changed, but in a way that should be considered identical (used rarely).
| ChangedRecomputeSame -- ^ I recomputed the value and it was the same.
| ChangedRecomputeDiff -- ^ I recomputed the value and it was different.
deriving (Eq,Show)
instance NFData RunChanged where rnf x = x `seq` ()
-- | The result of 'BuiltinRun'.
data RunResult value = RunResult
{runChanged :: RunChanged
-- ^ How has the 'RunResult' changed from what happened last time.
,runStore :: BS.ByteString
-- ^ The value to store in the Shake database.
,runValue :: value
-- ^ The value to return from 'Development.Shake.Rule.apply'.
} deriving Functor
instance NFData value => NFData (RunResult value) where
rnf (RunResult x1 x2 x3) = rnf x1 `seq` x2 `seq` rnf x3
---------------------------------------------------------------------
-- INSTANCES
instance Semigroup a => Semigroup (Rules a) where
a <> b = liftA2 (<>) a b
instance Monoid a => Monoid (Rules a) where
mempty = pure mempty

View File

@ -4,7 +4,7 @@ module Development.IDE.Graph.Rule(
-- * Defining builtin rules
-- | Functions and types for defining new types of Shake rules.
addRule,
Shake.RunMode(..), Shake.RunChanged(..), Shake.RunResult(..),
RunMode(..), RunChanged(..), RunResult(..),
-- * Calling builtin rules
-- | Wrappers around calling Shake rules. In general these should be specialised to a builtin rule.
apply, apply1,
@ -12,4 +12,4 @@ module Development.IDE.Graph.Rule(
import Development.IDE.Graph.Internal.Action
import Development.IDE.Graph.Internal.Rules
import qualified Development.Shake.Rule as Shake
import Development.IDE.Graph.Internal.Types

12
hls-graph/src/Paths.hs Normal file
View File

@ -0,0 +1,12 @@
-- | Fake cabal module for local building
module Paths_hls_graph(getDataDir, version) where
import Data.Version.Extra
-- If hls_graph can't find files in the data directory it tries relative to the executable
getDataDir :: IO FilePath
getDataDir = pure "random_path_that_cannot_possibly_exist"
version :: Version
version = makeVersion [0,0]

View File

@ -45,7 +45,7 @@ library
, dlist
, ghc
, hashable
, hls-graph ^>=1.4
, hls-graph >=1.4 && < 1.6
, hslogger
, lens
, lsp ^>=1.2.0.1

View File

@ -19,9 +19,11 @@ module Test.Hls
runSessionWithServerFormatter,
runSessionWithServer',
waitForProgressDone,
waitForAllProgressDone,
PluginDescriptor,
IdeState,
)
waitForBuildQueue
)
where
import Control.Applicative.Combinators
@ -30,6 +32,7 @@ import Control.Concurrent.Extra
import Control.Exception.Base
import Control.Monad (unless)
import Control.Monad.IO.Class
import Data.Aeson (Value (Null), toJSON)
import Data.ByteString.Lazy (ByteString)
import Data.Default (def)
import qualified Data.Text as T
@ -41,6 +44,7 @@ import Development.IDE.Graph (ShakeOptions (shakeThreads))
import Development.IDE.Main
import qualified Development.IDE.Main as Ghcide
import qualified Development.IDE.Plugin.HLS.GhcIde as Ghcide
import Development.IDE.Plugin.Test (TestRequest (WaitForShakeQueue))
import Development.IDE.Types.Options
import GHC.IO.Handle
import Ide.Plugin.Config (Config, formattingProvider)
@ -195,3 +199,26 @@ waitForProgressDone = loop
_ -> Nothing
done <- null <$> getIncompleteProgressSessions
unless done loop
-- | Wait for all progress to be done
-- Needs at least one progress done notification to return
waitForAllProgressDone :: Session ()
waitForAllProgressDone = loop
where
loop = do
~() <- skipManyTill anyMessage $ satisfyMaybe $ \case
FromServerMess SProgress (NotificationMessage _ _ (ProgressParams _ (End _))) -> Just ()
_ -> Nothing
done <- null <$> getIncompleteProgressSessions
unless done loop
-- | Wait for the build queue to be empty
waitForBuildQueue :: Session Seconds
waitForBuildQueue = do
let m = SCustomMethod "test"
waitId <- sendRequest m (toJSON WaitForShakeQueue)
(td, resp) <- duration $ skipManyTill anyMessage $ responseForId m waitId
case resp of
ResponseMessage{_result=Right Null} -> return td
-- assume a ghcide binary lacking the WaitForShakeQueue method
_ -> return 0

View File

@ -18,7 +18,6 @@ import Control.DeepSeq (NFData)
import Control.Monad.IO.Class
import Control.Monad.Trans.Maybe
import Data.Aeson
import Data.Binary
import Data.Functor
import qualified Data.HashMap.Strict as Map
import Data.Hashable
@ -71,7 +70,6 @@ data Example = Example
deriving (Eq, Show, Typeable, Generic)
instance Hashable Example
instance NFData Example
instance Binary Example
type instance RuleResult Example = ()

View File

@ -18,7 +18,6 @@ import Control.DeepSeq (NFData)
import Control.Monad.IO.Class
import Control.Monad.Trans.Maybe
import Data.Aeson
import Data.Binary
import Data.Functor
import qualified Data.HashMap.Strict as Map
import Data.Hashable
@ -63,7 +62,6 @@ data Example2 = Example2
deriving (Eq, Show, Typeable, Generic)
instance Hashable Example2
instance NFData Example2
instance Binary Example2
type instance RuleResult Example2 = ()

View File

@ -166,8 +166,6 @@ instance Hashable MinimalImports
instance NFData MinimalImports
instance Binary MinimalImports
type instance RuleResult MinimalImports = MinimalImportsResult
newtype MinimalImportsResult = MinimalImportsResult

View File

@ -35,7 +35,6 @@ import Control.Monad.Trans.Except
import Data.Aeson.Types (FromJSON (..),
ToJSON (..),
Value (..))
import Data.Binary
import Data.Default
import qualified Data.HashMap.Strict as Map
import Data.Hashable
@ -140,7 +139,6 @@ data GetHlintDiagnostics = GetHlintDiagnostics
deriving (Eq, Show, Typeable, Generic)
instance Hashable GetHlintDiagnostics
instance NFData GetHlintDiagnostics
instance Binary GetHlintDiagnostics
type instance RuleResult GetHlintDiagnostics = ()
@ -286,7 +284,6 @@ instance NFData Classify where rnf = rwhnf
instance NFData ParseFlags where rnf = rwhnf
instance Show Hint where show = const "<hint>"
instance Show ParseFlags where show = const "<parseFlags>"
instance Binary GetHlintSettings
type instance RuleResult GetHlintSettings = (ParseFlags, [Classify], Hint)

View File

@ -155,7 +155,6 @@ data RefineImports = RefineImports
instance Hashable RefineImports
instance NFData RefineImports
instance Binary RefineImports
type instance RuleResult RefineImports = RefineImportsResult
newtype RefineImportsResult = RefineImportsResult

View File

@ -39,7 +39,7 @@ import qualified Development.IDE.GHC.Compat.Util as FastString
import Development.IDE.GHC.Error (realSrcSpanToRange)
import Development.IDE.GHC.ExactPrint
import Development.IDE.Graph (Action, RuleResult, Rules, action)
import Development.IDE.Graph.Classes (Binary, Hashable, NFData)
import Development.IDE.Graph.Classes (Hashable, NFData)
import Development.IDE.Spans.LocalBindings (Bindings, getDefiningBindings)
import GHC.Generics (Generic)
import Generics.SYB hiding (Generic)
@ -84,7 +84,7 @@ runIde herald action state = runAction ("Wingman." <> herald <> "." <> action) s
runCurrentIde
:: forall a r
. ( r ~ RuleResult a
, Eq a , Hashable a , Binary a , Show a , Typeable a , NFData a
, Eq a , Hashable a , Show a , Typeable a , NFData a
, Show r, Typeable r, NFData r
)
=> String
@ -99,7 +99,7 @@ runCurrentIde herald state nfp a =
runStaleIde
:: forall a r
. ( r ~ RuleResult a
, Eq a , Hashable a , Binary a , Show a , Typeable a , NFData a
, Eq a , Hashable a , Show a , Typeable a , NFData a
, Show r, Typeable r, NFData r
)
=> String
@ -114,7 +114,7 @@ runStaleIde herald state nfp a =
unsafeRunStaleIde
:: forall a r
. ( r ~ RuleResult a
, Eq a , Hashable a , Binary a , Show a , Typeable a , NFData a
, Eq a , Hashable a , Show a , Typeable a , NFData a
, Show r, Typeable r, NFData r
)
=> String
@ -519,7 +519,6 @@ data WriteDiagnostics = WriteDiagnostics
instance Hashable WriteDiagnostics
instance NFData WriteDiagnostics
instance Binary WriteDiagnostics
type instance RuleResult WriteDiagnostics = ()

View File

@ -10,7 +10,7 @@ module Utils where
import Control.DeepSeq (deepseq)
import qualified Control.Exception as E
import Control.Lens hiding (List, failing, (<.>), (.=))
import Control.Monad (unless)
import Control.Monad (unless, void)
import Control.Monad.IO.Class
import Data.Aeson
import Data.Foldable
@ -85,6 +85,7 @@ mkTest name fp line col ts = it name $ do
runSessionForTactics $ do
doc <- openDoc (fp <.> "hs") "haskell"
_ <- waitForDiagnostics
waitForAllProgressDone
actions <- getCodeActions doc $ pointRange line col
let titles = mapMaybe codeActionTitle actions
for_ ts $ \(f, tc, var) -> do
@ -107,19 +108,24 @@ mkGoldenTest eq tc occ line col input =
resetGlobalHoleRef
runSessionForTactics $ do
doc <- openDoc (input <.> "hs") "haskell"
-- wait for diagnostics to start coming
_ <- waitForDiagnostics
-- wait for the entire build to finish, so that Tactics code actions that
-- use stale data will get uptodate stuff
void waitForBuildQueue
actions <- getCodeActions doc $ pointRange line col
Just (InR CodeAction {_command = Just c})
<- pure $ find ((== Just (tacticTitle tc occ)) . codeActionTitle) actions
executeCommand c
_resp <- skipManyTill anyMessage (message SWorkspaceApplyEdit)
edited <- documentContents doc
let expected_name = input <.> "expected" <.> "hs"
-- Write golden tests if they don't already exist
liftIO $ (doesFileExist expected_name >>=) $ flip unless $ do
T.writeFile expected_name edited
expected <- liftIO $ T.readFile expected_name
liftIO $ edited `eq` expected
case find ((== Just (tacticTitle tc occ)) . codeActionTitle) actions of
Just (InR CodeAction {_command = Just c}) -> do
executeCommand c
_resp <- skipManyTill anyMessage (message SWorkspaceApplyEdit)
edited <- documentContents doc
let expected_name = input <.> "expected" <.> "hs"
-- Write golden tests if they don't already exist
liftIO $ (doesFileExist expected_name >>=) $ flip unless $ do
T.writeFile expected_name edited
expected <- liftIO $ T.readFile expected_name
liftIO $ edited `eq` expected
_ -> error $ show actions
mkCodeLensTest

View File

@ -106,6 +106,7 @@ runLspMode ghcideArgs@GhcideArguments{..} idePlugins = do
{ Main.argCommand = argsCommand
, Main.argsHlsPlugins = idePlugins
, Main.argsLogger = pure hlsLogger
, Main.argsThreads = if argsThreads == 0 then Nothing else Just $ fromIntegral argsThreads
, Main.argsIdeOptions = \_config sessionLoader ->
let defOptions = Ghcide.defaultIdeOptions sessionLoader
in defOptions