@@ -72,8 +72,8 @@ getDatabaseValueGeneric k = do
7272-- NEW STYLE PRIMITIVES
7373
7474-- | Lookup the value for a single Id, may need to spawn it
75- lookupOne :: Global -> Stack -> Database -> Maybe Float -> Id -> Wait Locked (Either SomeException (Result (Value , BS_Store )))
76- lookupOne global stack database est i = do
75+ lookupOne :: Global -> Stack -> Database -> Id -> Wait Locked (Either SomeException (Result (Value , BS_Store )))
76+ lookupOne global stack database i = do
7777 res <- quickly $ liftIO $ getKeyValueFromId database i
7878 case res of
7979 Nothing -> Now $ Left $ errorStructured " Shake Id no longer exists" [(" Id" , Just $ show i)] " "
@@ -89,22 +89,22 @@ lookupOne global stack database est i = do
8989 Running (NoShow w) r -> do
9090 let w2 v = w v >> continue v
9191 setMem database i k $ Running (NoShow w2) r
92- Loaded r -> buildOne global stack database est i k (Just r) `fromLater` continue
93- Missing -> buildOne global stack database est i k Nothing `fromLater` continue
92+ Loaded r -> buildOne global stack database i k (Just r) `fromLater` continue
93+ Missing -> buildOne global stack database i k Nothing `fromLater` continue
9494
9595
9696-- | Build a key, must currently be either Loaded or Missing, changes to Waiting
97- buildOne :: Global -> Stack -> Database -> Maybe Float -> Id -> Key -> Maybe (Result BS. ByteString ) -> Wait Locked (Either SomeException (Result (Value , BS_Store )))
98- buildOne global@ Global {.. } stack database est i k r = case addStack i k stack of
97+ buildOne :: Global -> Stack -> Database -> Id -> Key -> Maybe (Result BS. ByteString ) -> Wait Locked (Either SomeException (Result (Value , BS_Store )))
98+ buildOne global@ Global {.. } stack database i k r = case addStack i k stack of
9999 Left e -> do
100100 quickly $ setIdKeyStatus global database i k $ mkError e
101101 pure $ Left e
102102 Right stack -> Later $ \ continue -> do
103103 setIdKeyStatus global database i k (Running (NoShow continue) r)
104104 let go = buildRunMode global stack database r
105- priority = case est of
105+ priority = case r of
106106 Nothing -> PoolStart
107- Just t -> PoolEstimate t (show k)
107+ Just (execution -> t) -> PoolEstimate t (show k)
108108 fromLater go $ \ mode -> liftIO $ addPool priority globalPool $
109109 runKey global stack k r mode $ \ res -> do
110110 runLocked database $ do
@@ -136,7 +136,7 @@ buildRunMode global stack database me = do
136136-- | Have the dependencies changed
137137buildRunDependenciesChanged :: Global -> Stack -> Database -> Result a -> Wait Locked Bool
138138buildRunDependenciesChanged global stack database me = isJust <$> firstJustM id
139- [firstJustWaitUnordered (fmap test . lookupOne global stack database ( Just $ execution me) ) x | Depends x <- depends me]
139+ [firstJustWaitUnordered (fmap test . lookupOne global stack database) x | Depends x <- depends me]
140140 where
141141 test (Right dep) | changed dep <= built me = Nothing
142142 test _ = Just ()
@@ -162,7 +162,7 @@ applyKeyValue callStack ks = do
162162 (is, wait) <- liftIO $ runLocked database $ do
163163 is <- mapM (mkId database) ks
164164 wait <- runWait $ do
165- x <- firstJustWaitUnordered (fmap (either Just (const Nothing )) . lookupOne global stack database Nothing ) $ nubOrd is
165+ x <- firstJustWaitUnordered (fmap (either Just (const Nothing )) . lookupOne global stack database) $ nubOrd is
166166 case x of
167167 Just e -> pure $ Left e
168168 Nothing -> quickly $ Right <$> mapM (fmap (\ (Just (_, Ready r)) -> fst $ result r) . liftIO . getKeyValueFromId database) is
@@ -267,7 +267,7 @@ historyLoad (Ver -> ver) = do
267267 let ask k = do
268268 i <- quickly $ mkId database k
269269 let identify = runIdentify globalRules k . fst . result
270- either (const Nothing ) identify <$> lookupOne global localStack database Nothing i
270+ either (const Nothing ) identify <$> lookupOne global localStack database i
271271 x <- case globalShared of
272272 Nothing -> pure Nothing
273273 Just shared -> lookupShared shared ask key localBuiltinVersion ver
0 commit comments