mirror of
https://github.com/ilyakooo0/urbit.git
synced 2024-12-02 07:06:41 +03:00
Merge pull request #3981 from urbit/jb/vere-versions
vere: adds versions to all pier artifacts
This commit is contained in:
commit
98c0c4a669
21
pkg/hs/urbit-eventlog-lmdb/lib/Urbit/EventLog/Event.hs
Normal file
21
pkg/hs/urbit-eventlog-lmdb/lib/Urbit/EventLog/Event.hs
Normal file
@ -0,0 +1,21 @@
|
||||
module Urbit.EventLog.Event
|
||||
( buildLogEvent
|
||||
, parseLogEvent
|
||||
)
|
||||
where
|
||||
|
||||
import ClassyPrelude
|
||||
import Data.Serialize
|
||||
import Urbit.Noun
|
||||
|
||||
buildLogEvent :: Mug -> Noun -> ByteString
|
||||
buildLogEvent mug noun = (runPut $ putWord32le mug) ++ (jamBS noun)
|
||||
|
||||
parseLogEvent :: MonadIO m => ByteString -> m (Mug, Noun)
|
||||
parseLogEvent bs = do
|
||||
let (prefix, suffix) = splitAt 4 bs
|
||||
let mug = case runGet getWord32le prefix of
|
||||
Left _ -> error "Impossible misread of word32 in parseLogEvent"
|
||||
Right x -> x
|
||||
n <- cueBSExn suffix
|
||||
pure (mug, n)
|
@ -31,8 +31,10 @@ import Foreign.Ptr (Ptr, castPtr, nullPtr)
|
||||
import Foreign.Storable (peek, poke, sizeOf)
|
||||
import RIO (HasLogFunc, RIO, display, logDebug, runRIO)
|
||||
import Urbit.Noun (DecodeErr, Noun, Ship)
|
||||
import Urbit.Noun (deriveNoun, fromNounExn, toNoun)
|
||||
import Urbit.Noun (cueBS, jamBS)
|
||||
import Urbit.Noun (deriveNoun, fromNounExn, toNoun, fromNoun)
|
||||
import Urbit.Noun (atomBytes, bytesAtom)
|
||||
import Urbit.Noun.Core (pattern Atom)
|
||||
|
||||
|
||||
import qualified Data.ByteString.Unsafe as BU
|
||||
import qualified Data.Vector as V
|
||||
@ -74,6 +76,8 @@ lastEv = readTVar . numEvents
|
||||
|
||||
data EventLogExn
|
||||
= NoLogIdentity
|
||||
| MissingLogVersion
|
||||
| BadLogVersion Word64
|
||||
| MissingEvent Word64
|
||||
| BadNounInLogIdentity ByteString DecodeErr ByteString
|
||||
| BadKeyInEventLog
|
||||
@ -207,26 +211,35 @@ getIdent env dbi = do
|
||||
Nothing -> throwIO NoLogIdentity
|
||||
Just li -> pure li
|
||||
where
|
||||
decodeIdent :: (Noun, Noun, Noun) -> RIO e LogIdentity
|
||||
decodeIdent = fromNounExn . toNoun
|
||||
decodeIdent :: (Noun, Noun, Noun, Noun) -> RIO e LogIdentity
|
||||
decodeIdent (ver, who, fake, life) = do
|
||||
-- Verify log version
|
||||
case fromNoun ver of
|
||||
Just 1 -> pure ()
|
||||
Just x -> throwIO $ BadLogVersion x
|
||||
Nothing -> throwIO $ MissingLogVersion
|
||||
|
||||
getTbl :: Env -> RIO e (Maybe (Noun, Noun, Noun))
|
||||
fromNounExn $ toNoun (who, fake, life)
|
||||
|
||||
getTbl :: Env -> RIO e (Maybe (Noun, Noun, Noun, Noun))
|
||||
getTbl env = do
|
||||
rwith (readTxn env) $ \txn -> do
|
||||
version <- getMb txn dbi "version"
|
||||
who <- getMb txn dbi "who"
|
||||
fake <- getMb txn dbi "is-fake"
|
||||
fake <- getMb txn dbi "fake"
|
||||
life <- getMb txn dbi "life"
|
||||
pure $ (,,) <$> who <*> fake <*> life
|
||||
pure $ (,,,) <$> version <*> who <*> fake <*> life
|
||||
|
||||
writeIdent :: HasLogFunc e => Env -> Dbi -> LogIdentity -> RIO e ()
|
||||
writeIdent env metaTbl ident@LogIdentity{..} = do
|
||||
logDebug "Writing log identity"
|
||||
let flags = compileWriteFlags []
|
||||
rwith (writeTxn env) $ \txn -> do
|
||||
x <- putNoun flags txn metaTbl "who" (toNoun who)
|
||||
y <- putNoun flags txn metaTbl "is-fake" (toNoun isFake)
|
||||
z <- putNoun flags txn metaTbl "life" (toNoun lifecycleLen)
|
||||
unless (x && y && z) $ do
|
||||
w <- putAtom flags txn metaTbl "version" (toNoun (1 :: Integer))
|
||||
x <- putAtom flags txn metaTbl "who" (toNoun who)
|
||||
y <- putAtom flags txn metaTbl "fake" (toNoun isFake)
|
||||
z <- putAtom flags txn metaTbl "life" (toNoun lifecycleLen)
|
||||
unless (w && x && y && z) $ do
|
||||
throwIO (BadWriteLogIdentity ident)
|
||||
|
||||
|
||||
@ -395,9 +408,6 @@ assertExn :: Exception e => Bool -> e -> IO ()
|
||||
assertExn True _ = pure ()
|
||||
assertExn False e = throwIO e
|
||||
|
||||
eitherExn :: Exception e => Either a b -> (a -> e) -> IO b
|
||||
eitherExn eat exn = either (throwIO . exn) pure eat
|
||||
|
||||
byteStringAsMdbVal :: ByteString -> (MDB_val -> IO a) -> IO a
|
||||
byteStringAsMdbVal bs k =
|
||||
BU.unsafeUseAsCStringLen bs $ \(ptr,sz) ->
|
||||
@ -435,17 +445,17 @@ mdbValToBytes (MDB_val sz ptr) = do
|
||||
|
||||
mdbValToNoun :: ByteString -> MDB_val -> IO Noun
|
||||
mdbValToNoun key (MDB_val sz ptr) = do
|
||||
bs <- BU.unsafePackCStringLen (castPtr ptr, fromIntegral sz)
|
||||
let res = cueBS bs
|
||||
eitherExn res (\err -> BadNounInLogIdentity key err bs)
|
||||
(Atom . bytesAtom) <$> BU.unsafePackCStringLen (castPtr ptr, fromIntegral sz)
|
||||
|
||||
putNoun :: MonadIO m
|
||||
putAtom :: MonadIO m
|
||||
=> MDB_WriteFlags -> Txn -> Dbi -> ByteString -> Noun -> m Bool
|
||||
putNoun flags txn db key val =
|
||||
io $
|
||||
byteStringAsMdbVal key $ \mKey ->
|
||||
byteStringAsMdbVal (jamBS val) $ \mVal ->
|
||||
mdb_put flags txn db mKey mVal
|
||||
putAtom flags txn db key val =
|
||||
case val of
|
||||
Atom a -> io $
|
||||
byteStringAsMdbVal key $ \mKey ->
|
||||
byteStringAsMdbVal (atomBytes a) $ \mVal ->
|
||||
mdb_put flags txn db mKey mVal
|
||||
_ -> error "Impossible putAtom received cell"
|
||||
|
||||
putBytes :: MonadIO m
|
||||
=> MDB_WriteFlags -> Txn -> Dbi -> Word64 -> ByteString -> m Bool
|
||||
|
@ -14,6 +14,7 @@ library:
|
||||
|
||||
dependencies:
|
||||
- base
|
||||
- cereal
|
||||
- classy-prelude
|
||||
- stm
|
||||
- rio
|
||||
|
@ -15,6 +15,7 @@ import Urbit.Vere.Pier.Types
|
||||
|
||||
import Control.Monad.Trans.Maybe (MaybeT(..))
|
||||
import Urbit.EventLog.LMDB (EventLog)
|
||||
import Urbit.EventLog.Event (parseLogEvent)
|
||||
|
||||
import qualified Data.Conduit.Combinators as C
|
||||
import qualified Urbit.EventLog.LMDB as Log
|
||||
@ -186,8 +187,8 @@ peekEffect log eId = runMaybeT $ do
|
||||
|
||||
peekEvent :: HasLogFunc e => EventLog -> Word64 -> RIO e (Maybe Event)
|
||||
peekEvent log eId = runMaybeT $ do
|
||||
octs <- MaybeT $ runConduit (Log.streamEvents log eId .| C.head)
|
||||
noun <- io $ cueBSExn octs
|
||||
(m,w,e) <- io $ fromNounExn noun
|
||||
ovum <- fromNounExn e
|
||||
octs <- MaybeT $ runConduit (Log.streamEvents log eId .| C.head)
|
||||
(m,n) <- io $ parseLogEvent octs
|
||||
(w,e) <- io $ fromNounExn n
|
||||
ovum <- fromNounExn e
|
||||
pure (Event eId m w ovum)
|
||||
|
@ -1,325 +0,0 @@
|
||||
{-|
|
||||
Low-Level Inferface for LMDB Event Log.
|
||||
-}
|
||||
|
||||
module Urbit.Vere.LMDB where
|
||||
|
||||
import Urbit.Prelude hiding (init)
|
||||
|
||||
import Data.RAcquire
|
||||
import Database.LMDB.Raw
|
||||
import Foreign.Marshal.Alloc
|
||||
import Foreign.Ptr
|
||||
import Urbit.Vere.Pier.Types
|
||||
|
||||
import Foreign.Storable (peek, poke, sizeOf)
|
||||
|
||||
import qualified Data.ByteString.Unsafe as BU
|
||||
|
||||
|
||||
-- Types -----------------------------------------------------------------------
|
||||
|
||||
type Env = MDB_env
|
||||
type Val = MDB_val
|
||||
type Txn = MDB_txn
|
||||
type Dbi = MDB_dbi
|
||||
type Cur = MDB_cursor
|
||||
|
||||
data VereLMDBExn
|
||||
= NoLogIdentity
|
||||
| MissingEvent EventId
|
||||
| BadNounInLogIdentity ByteString DecodeErr ByteString
|
||||
| BadKeyInEventLog
|
||||
| BadWriteLogIdentity LogIdentity
|
||||
| BadWriteEvent EventId
|
||||
| BadWriteEffect EventId
|
||||
deriving Show
|
||||
|
||||
instance Exception VereLMDBExn where
|
||||
|
||||
|
||||
-- Transactions ----------------------------------------------------------------
|
||||
|
||||
{-|
|
||||
A read-only transaction that commits at the end.
|
||||
|
||||
Use this when opening database handles.
|
||||
-}
|
||||
openTxn :: Env -> RAcquire e Txn
|
||||
openTxn env = mkRAcquire begin commit
|
||||
where
|
||||
begin = io $ mdb_txn_begin env Nothing True
|
||||
commit = io . mdb_txn_commit
|
||||
|
||||
{-|
|
||||
A read-only transaction that aborts at the end.
|
||||
|
||||
Use this when reading data from already-opened databases.
|
||||
-}
|
||||
readTxn :: Env -> RAcquire e Txn
|
||||
readTxn env = mkRAcquire begin abort
|
||||
where
|
||||
begin = io $ mdb_txn_begin env Nothing True
|
||||
abort = io . mdb_txn_abort
|
||||
|
||||
{-|
|
||||
A read-write transaction that commits upon sucessful completion and
|
||||
aborts on exception.
|
||||
|
||||
Use this when reading data from already-opened databases.
|
||||
-}
|
||||
writeTxn :: Env -> RAcquire e Txn
|
||||
writeTxn env = mkRAcquireType begin finalize
|
||||
where
|
||||
begin = io $ mdb_txn_begin env Nothing False
|
||||
finalize txn = io . \case
|
||||
ReleaseNormal -> mdb_txn_commit txn
|
||||
ReleaseEarly -> mdb_txn_commit txn
|
||||
ReleaseException -> mdb_txn_abort txn
|
||||
|
||||
|
||||
-- Cursors ---------------------------------------------------------------------
|
||||
|
||||
cursor :: Txn -> Dbi -> RAcquire e Cur
|
||||
cursor txn dbi = mkRAcquire open close
|
||||
where
|
||||
open = io $ mdb_cursor_open txn dbi
|
||||
close = io . mdb_cursor_close
|
||||
|
||||
|
||||
-- Last Key In Dbi -------------------------------------------------------------
|
||||
|
||||
lastKeyWord64 :: Env -> Dbi -> Txn -> RIO e Word64
|
||||
lastKeyWord64 env dbi txn =
|
||||
rwith (cursor txn dbi) $ \cur ->
|
||||
withKVPtrs' nullVal nullVal $ \pKey pVal ->
|
||||
io $ mdb_cursor_get MDB_LAST cur pKey pVal >>= \case
|
||||
False -> pure 0
|
||||
True -> peek pKey >>= mdbValToWord64
|
||||
|
||||
|
||||
-- Delete Rows -----------------------------------------------------------------
|
||||
|
||||
deleteAllRows :: Env -> Dbi -> RIO e ()
|
||||
deleteAllRows env dbi =
|
||||
rwith (writeTxn env) $ \txn ->
|
||||
rwith (cursor txn dbi) $ \cur ->
|
||||
withKVPtrs' nullVal nullVal $ \pKey pVal -> do
|
||||
let loop = io (mdb_cursor_get MDB_LAST cur pKey pVal) >>= \case
|
||||
False -> pure ()
|
||||
True -> do io $ mdb_cursor_del (compileWriteFlags []) cur
|
||||
loop
|
||||
loop
|
||||
|
||||
deleteRowsFrom :: HasLogFunc e => Env -> Dbi -> Word64 -> RIO e ()
|
||||
deleteRowsFrom env dbi start = do
|
||||
rwith (writeTxn env) $ \txn -> do
|
||||
last <- lastKeyWord64 env dbi txn
|
||||
for_ [start..last] $ \eId -> do
|
||||
withWordPtr eId $ \pKey -> do
|
||||
let key = MDB_val 8 (castPtr pKey)
|
||||
found <- io $ mdb_del txn dbi key Nothing
|
||||
unless found $
|
||||
throwIO (MissingEvent eId)
|
||||
|
||||
|
||||
-- Append Rows to Sequence -----------------------------------------------------
|
||||
|
||||
{-
|
||||
appendToSequence :: Env -> Dbi -> Vector ByteString -> RIO e ()
|
||||
appendToSequence env dbi events = do
|
||||
numEvs <- readIORef (numEvents log)
|
||||
next <- pure (numEvs + 1)
|
||||
doAppend $ zip [next..] $ toList events
|
||||
writeIORef (numEvents log) (numEvs + word (length events))
|
||||
where
|
||||
flags = compileWriteFlags [MDB_NOOVERWRITE]
|
||||
doAppend = \kvs ->
|
||||
rwith (writeTxn env) $ \txn ->
|
||||
for_ kvs $ \(k,v) -> do
|
||||
putBytes flags txn dbi k v >>= \case
|
||||
True -> pure ()
|
||||
False -> throwIO (BadWriteEvent k)
|
||||
-}
|
||||
|
||||
|
||||
-- Insert ----------------------------------------------------------------------
|
||||
|
||||
insertWord64 :: Env -> Dbi -> Word64 -> ByteString -> RIO e ()
|
||||
insertWord64 env dbi k v = do
|
||||
rwith (writeTxn env) $ \txn ->
|
||||
putBytes flags txn dbi k v >>= \case
|
||||
True -> pure ()
|
||||
False -> throwIO (BadWriteEffect k)
|
||||
where
|
||||
flags = compileWriteFlags []
|
||||
|
||||
|
||||
{-
|
||||
--------------------------------------------------------------------------------
|
||||
-- Read Events -----------------------------------------------------------------
|
||||
|
||||
streamEvents :: HasLogFunc e
|
||||
=> EventLog -> Word64
|
||||
-> ConduitT () ByteString (RIO e) ()
|
||||
streamEvents log first = do
|
||||
last <- lift $ lastEv log
|
||||
batch <- lift $ readBatch log first
|
||||
unless (null batch) $ do
|
||||
for_ batch yield
|
||||
streamEvents log (first + word (length batch))
|
||||
|
||||
streamEffectsRows :: forall e. HasLogFunc e
|
||||
=> EventLog -> EventId
|
||||
-> ConduitT () (Word64, ByteString) (RIO e) ()
|
||||
streamEffectsRows log = go
|
||||
where
|
||||
go :: EventId -> ConduitT () (Word64, ByteString) (RIO e) ()
|
||||
go next = do
|
||||
batch <- lift $ readRowsBatch (env log) (effectsTbl log) next
|
||||
unless (null batch) $ do
|
||||
for_ batch yield
|
||||
go (next + fromIntegral (length batch))
|
||||
|
||||
{-
|
||||
Read 1000 rows from the events table, starting from event `first`.
|
||||
|
||||
Throws `MissingEvent` if an event was missing from the log.
|
||||
-}
|
||||
readBatch :: EventLog -> Word64 -> RIO e (V.Vector ByteString)
|
||||
readBatch log first = start
|
||||
where
|
||||
start = do
|
||||
last <- lastEv log
|
||||
if (first > last)
|
||||
then pure mempty
|
||||
else readRows $ fromIntegral $ min 1000 $ ((last+1) - first)
|
||||
|
||||
assertFound :: EventId -> Bool -> RIO e ()
|
||||
assertFound id found = do
|
||||
unless found $ throwIO $ MissingEvent id
|
||||
|
||||
readRows count =
|
||||
withWordPtr first $ \pIdx ->
|
||||
withKVPtrs' (MDB_val 8 (castPtr pIdx)) nullVal $ \pKey pVal ->
|
||||
rwith (readTxn $ env log) $ \txn ->
|
||||
rwith (cursor txn $ eventsTbl log) $ \cur -> do
|
||||
assertFound first =<< io (mdb_cursor_get MDB_SET_KEY cur pKey pVal)
|
||||
fetchRows count cur pKey pVal
|
||||
|
||||
fetchRows count cur pKey pVal = do
|
||||
env <- ask
|
||||
V.generateM count $ \i -> runRIO env $ do
|
||||
key <- io $ peek pKey >>= mdbValToWord64
|
||||
val <- io $ peek pVal >>= mdbValToBytes
|
||||
idx <- pure (first + word i)
|
||||
unless (key == idx) $ throwIO $ MissingEvent idx
|
||||
when (count /= succ i) $ do
|
||||
assertFound idx =<< io (mdb_cursor_get MDB_NEXT cur pKey pVal)
|
||||
pure val
|
||||
|
||||
{-
|
||||
Read 1000 rows from the database, starting from key `first`.
|
||||
-}
|
||||
readRowsBatch :: forall e. HasLogFunc e
|
||||
=> Env -> Dbi -> Word64 -> RIO e (V.Vector (Word64, ByteString))
|
||||
readRowsBatch env dbi first = readRows
|
||||
where
|
||||
readRows = do
|
||||
logInfo $ display ("(readRowsBatch) From: " <> tshow first)
|
||||
withWordPtr first $ \pIdx ->
|
||||
withKVPtrs' (MDB_val 8 (castPtr pIdx)) nullVal $ \pKey pVal ->
|
||||
rwith (readTxn env) $ \txn ->
|
||||
rwith (cursor txn dbi) $ \cur ->
|
||||
io (mdb_cursor_get MDB_SET_RANGE cur pKey pVal) >>= \case
|
||||
False -> pure mempty
|
||||
True -> V.unfoldrM (fetchBatch cur pKey pVal) 1000
|
||||
|
||||
fetchBatch :: Cur -> Ptr Val -> Ptr Val -> Word
|
||||
-> RIO e (Maybe ((Word64, ByteString), Word))
|
||||
fetchBatch cur pKey pVal 0 = pure Nothing
|
||||
fetchBatch cur pKey pVal n = do
|
||||
key <- io $ peek pKey >>= mdbValToWord64
|
||||
val <- io $ peek pVal >>= mdbValToBytes
|
||||
io $ mdb_cursor_get MDB_NEXT cur pKey pVal >>= \case
|
||||
False -> pure $ Just ((key, val), 0)
|
||||
True -> pure $ Just ((key, val), pred n)
|
||||
|
||||
-}
|
||||
|
||||
-- Utils -----------------------------------------------------------------------
|
||||
|
||||
withKVPtrs' :: (MonadIO m, MonadUnliftIO m)
|
||||
=> Val -> Val -> (Ptr Val -> Ptr Val -> m a) -> m a
|
||||
withKVPtrs' k v cb =
|
||||
withRunInIO $ \run ->
|
||||
withKVPtrs k v $ \x y -> run (cb x y)
|
||||
|
||||
nullVal :: MDB_val
|
||||
nullVal = MDB_val 0 nullPtr
|
||||
|
||||
word :: Int -> Word64
|
||||
word = fromIntegral
|
||||
|
||||
assertExn :: Exception e => Bool -> e -> IO ()
|
||||
assertExn True _ = pure ()
|
||||
assertExn False e = throwIO e
|
||||
|
||||
eitherExn :: Exception e => Either a b -> (a -> e) -> IO b
|
||||
eitherExn eat exn = either (throwIO . exn) pure eat
|
||||
|
||||
byteStringAsMdbVal :: ByteString -> (MDB_val -> IO a) -> IO a
|
||||
byteStringAsMdbVal bs k =
|
||||
BU.unsafeUseAsCStringLen bs $ \(ptr,sz) ->
|
||||
k (MDB_val (fromIntegral sz) (castPtr ptr))
|
||||
|
||||
mdbValToWord64 :: MDB_val -> IO Word64
|
||||
mdbValToWord64 (MDB_val sz ptr) = do
|
||||
assertExn (sz == 8) BadKeyInEventLog
|
||||
peek (castPtr ptr)
|
||||
|
||||
withWord64AsMDBval :: (MonadIO m, MonadUnliftIO m)
|
||||
=> Word64 -> (MDB_val -> m a) -> m a
|
||||
withWord64AsMDBval w cb = do
|
||||
withWordPtr w $ \p ->
|
||||
cb (MDB_val (fromIntegral (sizeOf w)) (castPtr p))
|
||||
|
||||
withWordPtr :: (MonadIO m, MonadUnliftIO m)
|
||||
=> Word64 -> (Ptr Word64 -> m a) -> m a
|
||||
withWordPtr w cb =
|
||||
withRunInIO $ \run ->
|
||||
allocaBytes (sizeOf w) (\p -> poke p w >> run (cb p))
|
||||
|
||||
|
||||
-- Lower-Level Operations ------------------------------------------------------
|
||||
|
||||
getMb :: MonadIO m => Txn -> Dbi -> ByteString -> m (Maybe Noun)
|
||||
getMb txn db key =
|
||||
io $
|
||||
byteStringAsMdbVal key $ \mKey ->
|
||||
mdb_get txn db mKey >>= traverse (mdbValToNoun key)
|
||||
|
||||
mdbValToBytes :: MDB_val -> IO ByteString
|
||||
mdbValToBytes (MDB_val sz ptr) = do
|
||||
BU.unsafePackCStringLen (castPtr ptr, fromIntegral sz)
|
||||
|
||||
mdbValToNoun :: ByteString -> MDB_val -> IO Noun
|
||||
mdbValToNoun key (MDB_val sz ptr) = do
|
||||
bs <- BU.unsafePackCStringLen (castPtr ptr, fromIntegral sz)
|
||||
let res = cueBS bs
|
||||
eitherExn res (\err -> BadNounInLogIdentity key err bs)
|
||||
|
||||
putNoun :: MonadIO m
|
||||
=> MDB_WriteFlags -> Txn -> Dbi -> ByteString -> Noun -> m Bool
|
||||
putNoun flags txn db key val =
|
||||
io $
|
||||
byteStringAsMdbVal key $ \mKey ->
|
||||
byteStringAsMdbVal (jamBS val) $ \mVal ->
|
||||
mdb_put flags txn db mKey mVal
|
||||
|
||||
putBytes :: MonadIO m
|
||||
=> MDB_WriteFlags -> Txn -> Dbi -> Word64 -> ByteString -> m Bool
|
||||
putBytes flags txn db id bs = io $
|
||||
withWord64AsMDBval id $ \idVal ->
|
||||
byteStringAsMdbVal bs $ \mVal ->
|
||||
mdb_put flags txn db idVal mVal
|
@ -29,6 +29,7 @@ import System.Environment (getExecutablePath)
|
||||
import System.FilePath (splitFileName)
|
||||
import System.Posix.Files (ownerModes, setFileMode)
|
||||
import Urbit.EventLog.LMDB (EventLog)
|
||||
import Urbit.EventLog.Event (buildLogEvent)
|
||||
import Urbit.King.API (TermConn)
|
||||
import Urbit.Noun.Time (Wen)
|
||||
import Urbit.TermSize (TermSize(..), termSize)
|
||||
@ -103,11 +104,15 @@ writeJobs log !jobs = do
|
||||
fromJob (expectedId, job) = do
|
||||
unless (expectedId == jobId job) $ error $ show
|
||||
("bad job id!", expectedId, jobId job)
|
||||
pure $ jamBS $ jobPayload job
|
||||
pure $ buildLogEvent (jobMug job) (jobPayload job)
|
||||
|
||||
jobMug :: Job -> Mug
|
||||
jobMug (RunNok (LifeCyc _ m _)) = m
|
||||
jobMug (DoWork (Work _ m _ _)) = m
|
||||
|
||||
jobPayload :: Job -> Noun
|
||||
jobPayload (RunNok (LifeCyc _ m n)) = toNoun (m, n)
|
||||
jobPayload (DoWork (Work _ m d o )) = toNoun (m, d, o)
|
||||
jobPayload (RunNok (LifeCyc _ _ n)) = toNoun n
|
||||
jobPayload (DoWork (Work _ _ d o)) = toNoun (d, o)
|
||||
|
||||
|
||||
-- Acquire a running serf. -----------------------------------------------------
|
||||
@ -592,7 +597,7 @@ runPersist log inpQ out = do
|
||||
do
|
||||
unless (expectedId == eve) $ do
|
||||
throwIO (BadEventId expectedId eve)
|
||||
pure $ jamBS $ toNoun (mug, wen, non)
|
||||
pure $ buildLogEvent mug $ toNoun (wen, non)
|
||||
pure (fromList lis)
|
||||
|
||||
getBatchFromQueue :: STM (NonNull [(Fact, FX)])
|
||||
|
@ -19,6 +19,7 @@ import Urbit.Vere.Serf.IPC
|
||||
import Control.Monad.Trans.Resource (runResourceT)
|
||||
import Urbit.Arvo (FX)
|
||||
import Urbit.King.App.Class (HasStderrLogFunc(..))
|
||||
import Urbit.EventLog.Event (parseLogEvent)
|
||||
|
||||
import qualified Data.Conduit.Combinators as CC
|
||||
import qualified System.ProgressBar as PB
|
||||
@ -32,9 +33,6 @@ import qualified Urbit.Vere.Serf.IPC as X (Config (..), EvErr (..), Flag (..),
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
|
||||
parseLogRow :: MonadIO m => ByteString -> m (Mug, Noun)
|
||||
parseLogRow = cueBSExn >=> fromNounExn
|
||||
|
||||
withSerf :: HasLogFunc e => Config -> RAcquire e Serf
|
||||
withSerf config = mkRAcquire startup kill
|
||||
where
|
||||
@ -64,7 +62,7 @@ execReplay serf log last = do
|
||||
|
||||
evs <- runConduit $ Log.streamEvents log 1
|
||||
.| CC.take (fromIntegral bootSeqLen)
|
||||
.| CC.mapM (fmap snd . parseLogRow)
|
||||
.| CC.mapM (fmap snd . parseLogEvent)
|
||||
.| CC.sinkList
|
||||
|
||||
let numEvs = fromIntegral (length evs)
|
||||
@ -117,7 +115,7 @@ execReplay serf log last = do
|
||||
$ runConduit
|
||||
$ Log.streamEvents log (lastEventInSnap + 1)
|
||||
.| CC.take (fromIntegral numEvs)
|
||||
.| CC.mapM (fmap snd . parseLogRow)
|
||||
.| CC.mapM (fmap snd . parseLogEvent)
|
||||
.| replay 5 incProgress serf
|
||||
|
||||
res & \case
|
||||
@ -153,7 +151,7 @@ collectFX serf log = do
|
||||
runResourceT
|
||||
$ runConduit
|
||||
$ Log.streamEvents log (lastEv + 1)
|
||||
.| CC.mapM (parseLogRow >=> fromNounExn . snd)
|
||||
.| CC.mapM (parseLogEvent >=> fromNounExn . snd)
|
||||
.| swim serf
|
||||
.| persistFX log
|
||||
|
||||
|
@ -8,7 +8,7 @@ static void
|
||||
_setup(void)
|
||||
{
|
||||
u3m_init();
|
||||
u3m_pave(c3y, c3n);
|
||||
u3m_pave(c3y);
|
||||
}
|
||||
|
||||
/* _ames_writ_ex(): |hi packet from fake ~zod to fake ~nec
|
||||
|
@ -14,18 +14,18 @@
|
||||
/* u3e_control: memory change, control file.
|
||||
*/
|
||||
typedef struct _u3e_control {
|
||||
c3_d evt_d; // event number
|
||||
c3_w nor_w; // new page count north
|
||||
c3_w sou_w; // new page count south
|
||||
c3_w pgs_w; // number of changed pages
|
||||
c3_w ver_y; // version number
|
||||
c3_w nor_w; // new page count north
|
||||
c3_w sou_w; // new page count south
|
||||
c3_w pgs_w; // number of changed pages
|
||||
u3e_line mem_u[0]; // per page
|
||||
} u3e_control;
|
||||
|
||||
/* u3_cs_patch: memory change, top level.
|
||||
*/
|
||||
typedef struct _u3_cs_patch {
|
||||
c3_i ctl_i;
|
||||
c3_i mem_i;
|
||||
c3_i ctl_i;
|
||||
c3_i mem_i;
|
||||
u3e_control* con_u;
|
||||
} u3_ce_patch;
|
||||
|
||||
@ -40,11 +40,10 @@
|
||||
/* u3e_pool: entire memory system.
|
||||
*/
|
||||
typedef struct _u3e_pool {
|
||||
c3_c* dir_c; // path to
|
||||
c3_d evt_d; // last patch written at event
|
||||
c3_w dit_w[u3a_pages >> 5]; // touched since last save
|
||||
u3e_image nor_u; // north segment
|
||||
u3e_image sou_u; // south segment
|
||||
c3_c* dir_c; // path to
|
||||
c3_w dit_w[u3a_pages >> 5]; // touched since last save
|
||||
u3e_image nor_u; // north segment
|
||||
u3e_image sou_u; // south segment
|
||||
} u3e_pool;
|
||||
|
||||
|
||||
@ -55,6 +54,9 @@
|
||||
c3_global u3e_pool u3e_Pool;
|
||||
# define u3P u3e_Pool
|
||||
|
||||
/** Constants.
|
||||
**/
|
||||
# define u3e_version 1
|
||||
|
||||
/** Functions.
|
||||
**/
|
||||
|
@ -39,7 +39,7 @@
|
||||
/* u3m_pave(): instantiate or activate image.
|
||||
*/
|
||||
void
|
||||
u3m_pave(c3_o nuu_o, c3_o bug_o);
|
||||
u3m_pave(c3_o nuu_o);
|
||||
|
||||
/* u3m_file(): load file, as atom, or bail.
|
||||
*/
|
||||
|
@ -5,22 +5,22 @@
|
||||
/** Data structures.
|
||||
**/
|
||||
/* u3v_arvo: modern arvo structure.
|
||||
** NB: packed to perserve word alignment given [eve_d]
|
||||
*/
|
||||
typedef struct _u3v_arvo {
|
||||
c3_d ent_d; // event number
|
||||
typedef struct __attribute__((__packed__)) _u3v_arvo {
|
||||
c3_d eve_d; // event number
|
||||
u3_noun yot; // cached gates
|
||||
u3_noun now; // current time, as noun
|
||||
u3_noun wen; // current time, as text, XX remove
|
||||
u3_noun sev_l; // instance number
|
||||
u3_noun sen; // instance string
|
||||
u3_noun now; // current time
|
||||
u3_noun roc; // kernel core
|
||||
} u3v_arvo;
|
||||
|
||||
/* u3v_home: all internal (within image) state.
|
||||
** NB: version must be last for discriminability in north road
|
||||
*/
|
||||
typedef struct _u3v_home {
|
||||
u3a_road rod_u; // storage state
|
||||
u3v_arvo arv_u; // arvo state
|
||||
c3_w ver_w; // version number
|
||||
} u3v_home;
|
||||
|
||||
|
||||
@ -32,6 +32,10 @@
|
||||
# define u3H u3v_Home
|
||||
# define u3A (&(u3v_Home->arv_u))
|
||||
|
||||
/** Constants.
|
||||
**/
|
||||
# define u3v_version 1
|
||||
|
||||
/** Functions.
|
||||
**/
|
||||
/* u3v_life(): execute initial lifecycle, producing Arvo core.
|
||||
@ -59,11 +63,6 @@
|
||||
u3_noun
|
||||
u3v_wish(const c3_c* str_c);
|
||||
|
||||
/* u3v_numb(): set the instance number.
|
||||
*/
|
||||
void
|
||||
u3v_numb(void);
|
||||
|
||||
/* u3v_time(): set the reck time.
|
||||
*/
|
||||
void
|
||||
|
@ -353,7 +353,6 @@
|
||||
*/
|
||||
typedef struct _u3_fact {
|
||||
c3_d eve_d; // event number
|
||||
c3_l bug_l; // kernel mug before XX remove
|
||||
c3_l mug_l; // kernel mug after
|
||||
u3_noun job; // (pair date ovum)
|
||||
struct _u3_fact* nex_u; // next in queue
|
||||
|
@ -308,6 +308,14 @@ _ce_patch_verify(u3_ce_patch* pat_u)
|
||||
{
|
||||
c3_w i_w;
|
||||
|
||||
if ( u3e_version != pat_u->con_u->ver_y ) {
|
||||
fprintf(stderr, "loom: patch version mismatch: have %u, need %u\r\n",
|
||||
pat_u->con_u->ver_y,
|
||||
u3e_version);
|
||||
c3_assert(0);
|
||||
return c3n;
|
||||
}
|
||||
|
||||
for ( i_w = 0; i_w < pat_u->con_u->pgs_w; i_w++ ) {
|
||||
c3_w pag_w = pat_u->con_u->mem_u[i_w].pag_w;
|
||||
c3_w mug_w = pat_u->con_u->mem_u[i_w].mug_w;
|
||||
@ -571,6 +579,7 @@ _ce_patch_compose(void)
|
||||
|
||||
_ce_patch_create(pat_u);
|
||||
pat_u->con_u = c3_malloc(sizeof(u3e_control) + (pgs_w * sizeof(u3e_line)));
|
||||
pat_u->con_u->ver_y = u3e_version;
|
||||
pgc_w = 0;
|
||||
|
||||
for ( i_w = 0; i_w < nor_w; i_w++ ) {
|
||||
|
@ -438,66 +438,17 @@ u3m_file(c3_c* pas_c)
|
||||
}
|
||||
}
|
||||
|
||||
/* _find_north(): in restored image, point to a north home.
|
||||
/* u3m_mark(): mark all nouns in the road.
|
||||
*/
|
||||
static u3_road*
|
||||
_find_north(c3_w* mem_w, c3_w siz_w, c3_w len_w)
|
||||
c3_w
|
||||
u3m_mark(FILE* fil_u)
|
||||
{
|
||||
return (void *) ((mem_w + len_w) - siz_w);
|
||||
}
|
||||
|
||||
#if 0
|
||||
/* _find_south(): in restored image, point to a south home.
|
||||
*/
|
||||
static u3_road*
|
||||
_find_south(c3_w* mem_w, c3_w siz_w, c3_w len_w)
|
||||
{
|
||||
return (void *)mem_w;
|
||||
}
|
||||
#endif
|
||||
|
||||
static u3_road*
|
||||
_pave_north(c3_w* mem_w, c3_w siz_w, c3_w len_w)
|
||||
{
|
||||
c3_w* rut_w = mem_w;
|
||||
c3_w* hat_w = rut_w;
|
||||
c3_w* mat_w = ((mem_w + len_w) - siz_w);
|
||||
c3_w* cap_w = mat_w;
|
||||
u3_road* rod_u = (void*) mat_w;
|
||||
|
||||
// memset(mem_w, 0, 4 * len_w); // enable in case of corruption
|
||||
memset(rod_u, 0, 4 * siz_w);
|
||||
|
||||
rod_u->rut_p = u3of(c3_w, rut_w);
|
||||
rod_u->hat_p = u3of(c3_w, hat_w);
|
||||
|
||||
rod_u->mat_p = u3of(c3_w, mat_w);
|
||||
rod_u->cap_p = u3of(c3_w, cap_w);
|
||||
|
||||
return rod_u;
|
||||
}
|
||||
|
||||
/* _pave_south(): install a south road.
|
||||
*/
|
||||
static u3_road*
|
||||
_pave_south(c3_w* mem_w, c3_w siz_w, c3_w len_w)
|
||||
{
|
||||
c3_w* rut_w = (mem_w + len_w);
|
||||
c3_w* hat_w = rut_w;
|
||||
c3_w* mat_w = mem_w;
|
||||
c3_w* cap_w = mat_w + siz_w;
|
||||
u3_road* rod_u = (void*) mat_w;
|
||||
|
||||
// memset(mem_w, 0, 4 * len_w); // enable in case of corruption
|
||||
memset(rod_u, 0, 4 * siz_w);
|
||||
|
||||
rod_u->rut_p = u3of(c3_w, rut_w);
|
||||
rod_u->hat_p = u3of(c3_w, hat_w);
|
||||
|
||||
rod_u->mat_p = u3of(c3_w, mat_w);
|
||||
rod_u->cap_p = u3of(c3_w, cap_w);
|
||||
|
||||
return rod_u;
|
||||
c3_w tot_w = 0;
|
||||
tot_w += u3v_mark(fil_u);
|
||||
tot_w += u3j_mark(fil_u);
|
||||
tot_w += u3n_mark(fil_u);
|
||||
tot_w += u3a_mark_road(fil_u);
|
||||
return tot_w;
|
||||
}
|
||||
|
||||
/* _pave_parts(): build internal tables.
|
||||
@ -513,37 +464,122 @@ _pave_parts(void)
|
||||
u3R->byc.har_p = u3h_new();
|
||||
}
|
||||
|
||||
/* u3m_mark(): mark all nouns in the road.
|
||||
/* _pave_road(): initialize road boundaries
|
||||
*/
|
||||
c3_w
|
||||
u3m_mark(FILE* fil_u)
|
||||
static u3_road*
|
||||
_pave_road(c3_w* rut_w, c3_w* mat_w, c3_w* cap_w, c3_w siz_w)
|
||||
{
|
||||
c3_w tot_w = 0;
|
||||
tot_w += u3v_mark(fil_u);
|
||||
tot_w += u3j_mark(fil_u);
|
||||
tot_w += u3n_mark(fil_u);
|
||||
tot_w += u3a_mark_road(fil_u);
|
||||
return tot_w;
|
||||
u3_road* rod_u = (void*) mat_w;
|
||||
|
||||
// enable in case of corruption
|
||||
//
|
||||
// memset(mem_w, 0, 4 * len_w);
|
||||
memset(rod_u, 0, 4 * siz_w);
|
||||
|
||||
// the top and bottom of the heap are initially the same
|
||||
//
|
||||
rod_u->rut_p = u3of(c3_w, rut_w);
|
||||
rod_u->hat_p = u3of(c3_w, rut_w);
|
||||
|
||||
|
||||
rod_u->mat_p = u3of(c3_w, mat_w); // stack bottom
|
||||
rod_u->cap_p = u3of(c3_w, cap_w); // stack top
|
||||
|
||||
return rod_u;
|
||||
}
|
||||
|
||||
/* _pave_north(): calculate boundaries and initialize north road.
|
||||
*/
|
||||
static u3_road*
|
||||
_pave_north(c3_w* mem_w, c3_w siz_w, c3_w len_w)
|
||||
{
|
||||
// in a north road, the heap is low and the stack is high
|
||||
//
|
||||
// the heap starts at the base memory pointer [mem_w];
|
||||
// the stack starts at the end of the memory segment,
|
||||
// minus space for the road structure [siz_w]
|
||||
//
|
||||
c3_w* rut_w = mem_w;
|
||||
c3_w* mat_w = ((mem_w + len_w) - siz_w);
|
||||
c3_w* cap_w = mat_w;
|
||||
|
||||
return _pave_road(rut_w, mat_w, cap_w, siz_w);
|
||||
}
|
||||
|
||||
/* _pave_south(): calculate boundaries and initialize south road.
|
||||
*/
|
||||
static u3_road*
|
||||
_pave_south(c3_w* mem_w, c3_w siz_w, c3_w len_w)
|
||||
{
|
||||
// in a south road, the heap is high and the stack is low
|
||||
//
|
||||
// the heap starts at the end of the memory segment;
|
||||
// the stack starts at the base memory pointer [mem_w],
|
||||
// and ends after the space for the road structure [siz_w]
|
||||
//
|
||||
c3_w* rut_w = (mem_w + len_w);
|
||||
c3_w* mat_w = mem_w;
|
||||
c3_w* cap_w = mat_w + siz_w;
|
||||
|
||||
return _pave_road(rut_w, mat_w, cap_w, siz_w);
|
||||
}
|
||||
|
||||
/* _pave_home(): initialize pristine home road.
|
||||
*/
|
||||
static void
|
||||
_pave_home(void)
|
||||
{
|
||||
c3_w* mem_w = u3_Loom + 1;
|
||||
c3_w siz_w = c3_wiseof(u3v_home);
|
||||
c3_w len_w = u3a_words - 1;
|
||||
|
||||
u3H = (void *)_pave_north(mem_w, siz_w, len_w);
|
||||
u3H->ver_w = u3v_version;
|
||||
u3R = &u3H->rod_u;
|
||||
|
||||
_pave_parts();
|
||||
}
|
||||
|
||||
STATIC_ASSERT( ((c3_wiseof(u3v_home) * 4) == sizeof(u3v_home)),
|
||||
"home road alignment" );
|
||||
|
||||
/* _find_home(): in restored image, point to home road.
|
||||
*/
|
||||
static void
|
||||
_find_home(void)
|
||||
{
|
||||
// NB: the home road is always north
|
||||
//
|
||||
c3_w* mem_w = u3_Loom + 1;
|
||||
c3_w siz_w = c3_wiseof(u3v_home);
|
||||
c3_w len_w = u3a_words - 1;
|
||||
|
||||
{
|
||||
c3_w ver_w = *((mem_w + len_w) - 1);
|
||||
|
||||
if ( u3v_version != ver_w ) {
|
||||
fprintf(stderr, "loom: checkpoint version mismatch: "
|
||||
"have %u, need %u\r\n",
|
||||
ver_w,
|
||||
u3v_version);
|
||||
abort();
|
||||
}
|
||||
}
|
||||
|
||||
u3H = (void *)((mem_w + len_w) - siz_w);
|
||||
u3R = &u3H->rod_u;
|
||||
}
|
||||
|
||||
/* u3m_pave(): instantiate or activate image.
|
||||
*/
|
||||
void
|
||||
u3m_pave(c3_o nuu_o, c3_o bug_o)
|
||||
u3m_pave(c3_o nuu_o)
|
||||
{
|
||||
if ( c3y == nuu_o ) {
|
||||
u3H = (void *)_pave_north(u3_Loom + 1,
|
||||
c3_wiseof(u3v_home),
|
||||
u3a_words - 1);
|
||||
u3R = &u3H->rod_u;
|
||||
|
||||
_pave_parts();
|
||||
_pave_home();
|
||||
}
|
||||
else {
|
||||
u3H = (void *)_find_north(u3_Loom + 1,
|
||||
c3_wiseof(u3v_home),
|
||||
u3a_words - 1);
|
||||
u3R = &u3H->rod_u;
|
||||
_find_home();
|
||||
}
|
||||
}
|
||||
|
||||
@ -1676,7 +1712,7 @@ u3m_boot(c3_c* dir_c)
|
||||
|
||||
/* Construct or activate the allocator.
|
||||
*/
|
||||
u3m_pave(nuu_o, c3n);
|
||||
u3m_pave(nuu_o);
|
||||
|
||||
/* Initialize the jet system.
|
||||
*/
|
||||
@ -1687,19 +1723,11 @@ u3m_boot(c3_c* dir_c)
|
||||
|
||||
/* Reactivate jets on old kernel.
|
||||
*/
|
||||
if ( !_(nuu_o) ) {
|
||||
if ( c3n == nuu_o ) {
|
||||
u3j_ream();
|
||||
u3n_ream();
|
||||
|
||||
// XX unused, removed
|
||||
//
|
||||
// u3z() temporarily preserved to avoid leaking
|
||||
// checkpointed values
|
||||
//
|
||||
u3z(u3A->wen);
|
||||
u3A->wen = 0;
|
||||
|
||||
return u3A->ent_d;
|
||||
return u3A->eve_d;
|
||||
}
|
||||
else {
|
||||
/* Basic initialization.
|
||||
@ -1727,7 +1755,7 @@ u3m_boot_lite(void)
|
||||
|
||||
/* Construct or activate the allocator.
|
||||
*/
|
||||
u3m_pave(c3y, c3n);
|
||||
u3m_pave(c3y);
|
||||
|
||||
/* Initialize the jet system.
|
||||
*/
|
||||
|
@ -376,7 +376,7 @@ _cu_realloc(FILE* fil_u, ur_root_t** tor_u, ur_nvec_t* doc_u)
|
||||
|
||||
// stash event number
|
||||
//
|
||||
c3_d eve_d = u3A->ent_d;
|
||||
c3_d eve_d = u3A->eve_d;
|
||||
|
||||
// reallocate kernel and cold jet state
|
||||
//
|
||||
@ -395,7 +395,7 @@ _cu_realloc(FILE* fil_u, ur_root_t** tor_u, ur_nvec_t* doc_u)
|
||||
//
|
||||
// NB: hot jet state is not yet re-established
|
||||
//
|
||||
u3m_pave(c3y, c3n);
|
||||
u3m_pave(c3y);
|
||||
|
||||
// reallocate all nouns on the loom
|
||||
//
|
||||
@ -412,7 +412,7 @@ _cu_realloc(FILE* fil_u, ur_root_t** tor_u, ur_nvec_t* doc_u)
|
||||
|
||||
// restore event number
|
||||
//
|
||||
u3A->ent_d = eve_d;
|
||||
u3A->eve_d = eve_d;
|
||||
|
||||
// mark all pages dirty
|
||||
//
|
||||
@ -649,7 +649,14 @@ u3u_cram(c3_c* dir_c, c3_d eve_d)
|
||||
roc = ur_cons(rot_u, cod_u.refs[i_d], roc);
|
||||
}
|
||||
|
||||
roc = ur_cons(rot_u, ur_coin64(rot_u, c3__fast), ur_cons(rot_u, ken, roc));
|
||||
{
|
||||
c3_c* has_c = "hashboard";
|
||||
ur_nref has = ur_coin_bytes(rot_u, strlen(has_c), (c3_y*)has_c);
|
||||
roc = ur_cons(rot_u, has, roc);
|
||||
}
|
||||
|
||||
roc = ur_cons(rot_u, ur_coin64(rot_u, c3__arvo),
|
||||
ur_cons(rot_u, ken, roc));
|
||||
|
||||
ur_jam(rot_u, roc, &len_d, &byt_y);
|
||||
}
|
||||
@ -833,7 +840,7 @@ u3u_uncram(c3_c* dir_c, c3_d eve_d)
|
||||
//
|
||||
// NB: hot jet state is not yet re-established
|
||||
//
|
||||
u3m_pave(c3y, c3n);
|
||||
u3m_pave(c3y);
|
||||
|
||||
// cue rock, restore persistent state
|
||||
//
|
||||
@ -844,7 +851,7 @@ u3u_uncram(c3_c* dir_c, c3_d eve_d)
|
||||
//
|
||||
u3_cue_xeno* sil_u = u3s_cue_xeno_init_with(ur_fib33, ur_fib34);
|
||||
u3_weak ref = u3s_cue_xeno_with(sil_u, len_d, byt_y);
|
||||
u3_noun roc, cod;
|
||||
u3_noun roc, doc, tag, cod;
|
||||
|
||||
u3s_cue_xeno_done(sil_u);
|
||||
|
||||
@ -853,7 +860,10 @@ u3u_uncram(c3_c* dir_c, c3_d eve_d)
|
||||
c3_free(nam_c);
|
||||
return c3n;
|
||||
}
|
||||
else if ( c3n == u3r_pq(ref, c3__fast, &roc, &cod) ) {
|
||||
else if ( c3n == u3r_pq(ref, c3__arvo, &roc, &doc)
|
||||
|| (c3n == u3r_cell(doc, &tag, &cod))
|
||||
|| (c3n == u3r_sing_c("hashboard", tag)) )
|
||||
{
|
||||
fprintf(stderr, "uncram: failed: invalid rock format\r\n");
|
||||
u3z(ref);
|
||||
c3_free(nam_c);
|
||||
@ -875,7 +885,7 @@ u3u_uncram(c3_c* dir_c, c3_d eve_d)
|
||||
|
||||
// restore event number
|
||||
//
|
||||
u3A->ent_d = eve_d;
|
||||
u3A->eve_d = eve_d;
|
||||
|
||||
// mark all pages dirty
|
||||
//
|
||||
|
@ -166,16 +166,6 @@ u3v_time(u3_noun now)
|
||||
u3A->now = now;
|
||||
}
|
||||
|
||||
/* u3v_numb(): set the instance number.
|
||||
*/
|
||||
void
|
||||
u3v_numb()
|
||||
{
|
||||
u3A->sev_l = u3r_mug(u3A->now);
|
||||
u3z(u3A->sen);
|
||||
u3A->sen = _cv_scot(u3nc(c3__uv, u3A->sev_l));
|
||||
}
|
||||
|
||||
#if 0
|
||||
/* _cv_time_bump(): advance the reck time by a small increment.
|
||||
*/
|
||||
@ -315,8 +305,6 @@ u3v_mark(FILE* fil_u)
|
||||
|
||||
tot_w += u3a_maid(fil_u, " kernel", u3a_mark_noun(arv_u->roc));
|
||||
tot_w += u3a_maid(fil_u, " date", u3a_mark_noun(arv_u->now));
|
||||
tot_w += u3a_maid(fil_u, " formatted date", u3a_mark_noun(arv_u->wen));
|
||||
tot_w += u3a_maid(fil_u, " instance string", u3a_mark_noun(arv_u->sen));
|
||||
tot_w += u3a_maid(fil_u, " wish cache", u3a_mark_noun(arv_u->yot));
|
||||
return u3a_maid(fil_u, "total arvo stuff", tot_w);
|
||||
}
|
||||
@ -345,14 +333,10 @@ u3v_rewrite_compact()
|
||||
|
||||
u3a_rewrite_noun(arv_u->roc);
|
||||
u3a_rewrite_noun(arv_u->now);
|
||||
u3a_rewrite_noun(arv_u->wen);
|
||||
u3a_rewrite_noun(arv_u->sen);
|
||||
u3a_rewrite_noun(arv_u->yot);
|
||||
|
||||
arv_u->roc = u3a_rewritten_noun(arv_u->roc);
|
||||
arv_u->now = u3a_rewritten_noun(arv_u->now);
|
||||
arv_u->wen = u3a_rewritten_noun(arv_u->wen);
|
||||
arv_u->sen = u3a_rewritten_noun(arv_u->sen);
|
||||
arv_u->yot = u3a_rewritten_noun(arv_u->yot);
|
||||
}
|
||||
|
||||
|
@ -7,7 +7,7 @@ static void
|
||||
_setup(void)
|
||||
{
|
||||
u3m_init();
|
||||
u3m_pave(c3y, c3n);
|
||||
u3m_pave(c3y);
|
||||
}
|
||||
|
||||
/* _test_ames(): spot check ames helpers
|
||||
|
@ -9,7 +9,7 @@ static void
|
||||
_setup(void)
|
||||
{
|
||||
u3m_init();
|
||||
u3m_pave(c3y, c3n);
|
||||
u3m_pave(c3y);
|
||||
}
|
||||
|
||||
/* _test_bit_manipulation():
|
||||
|
@ -7,7 +7,7 @@ static void
|
||||
_setup(void)
|
||||
{
|
||||
u3m_init();
|
||||
u3m_pave(c3y, c3n);
|
||||
u3m_pave(c3y);
|
||||
}
|
||||
|
||||
static void
|
||||
|
@ -6,7 +6,7 @@ static void
|
||||
_setup(void)
|
||||
{
|
||||
u3m_init();
|
||||
u3m_pave(c3y, c3n);
|
||||
u3m_pave(c3y);
|
||||
}
|
||||
|
||||
static c3_i
|
||||
|
@ -6,7 +6,7 @@ static void
|
||||
_setup(void)
|
||||
{
|
||||
u3m_init();
|
||||
u3m_pave(c3y, c3n);
|
||||
u3m_pave(c3y);
|
||||
}
|
||||
|
||||
/* _test_mug(): spot check u3r_mug hashes.
|
||||
|
@ -7,7 +7,7 @@ static void
|
||||
_setup(void)
|
||||
{
|
||||
u3m_init();
|
||||
u3m_pave(c3y, c3n);
|
||||
u3m_pave(c3y);
|
||||
}
|
||||
|
||||
/* _newt_encode(): synchronous serialization into a single buffer, for test purposes
|
||||
|
@ -9,7 +9,7 @@ static void
|
||||
_setup(void)
|
||||
{
|
||||
u3m_init();
|
||||
u3m_pave(c3y, c3n);
|
||||
u3m_pave(c3y);
|
||||
}
|
||||
|
||||
/* _util_rand_string(): dynamically allocated len_w random string
|
||||
|
@ -165,31 +165,34 @@ _disk_commit_start(struct _cd_save* req_u)
|
||||
_disk_commit_after_cb);
|
||||
}
|
||||
|
||||
/* _disk_serialize_v0(): serialize events in format v0.
|
||||
/* _disk_serialize_v1(): serialize events in format v1.
|
||||
*/
|
||||
static c3_w
|
||||
_disk_serialize_v0(u3_fact* tac_u, c3_y** dat_y)
|
||||
_disk_serialize_v1(u3_fact* tac_u, c3_y** out_y)
|
||||
{
|
||||
u3_noun val = u3nc(tac_u->bug_l, u3k(tac_u->job));
|
||||
u3_atom mat;
|
||||
c3_w len_w;
|
||||
|
||||
#ifdef DISK_TRACE_JAM
|
||||
u3t_event_trace("king disk jam", 'B');
|
||||
#endif
|
||||
|
||||
mat = u3ke_jam(val);
|
||||
len_w = u3r_met(3, mat);
|
||||
*dat_y = c3_malloc(len_w);
|
||||
u3r_bytes(0, len_w, *dat_y, mat);
|
||||
{
|
||||
u3_atom mat = u3qe_jam(tac_u->job);
|
||||
c3_w len_w = u3r_met(3, mat);
|
||||
c3_y* dat_y = c3_malloc(4 + len_w);
|
||||
dat_y[0] = tac_u->mug_l & 0xff;
|
||||
dat_y[1] = (tac_u->mug_l >> 8) & 0xff;
|
||||
dat_y[2] = (tac_u->mug_l >> 16) & 0xff;
|
||||
dat_y[3] = (tac_u->mug_l >> 24) & 0xff;
|
||||
u3r_bytes(0, len_w, dat_y + 4, mat);
|
||||
|
||||
#ifdef DISK_TRACE_JAM
|
||||
u3t_event_trace("king disk jam", 'E');
|
||||
u3t_event_trace("king disk jam", 'E');
|
||||
#endif
|
||||
|
||||
u3z(mat);
|
||||
u3z(mat);
|
||||
|
||||
return len_w;
|
||||
*out_y = dat_y;
|
||||
return len_w + 4;
|
||||
}
|
||||
}
|
||||
|
||||
/* _disk_batch(): create a write batch
|
||||
@ -213,7 +216,7 @@ _disk_batch(u3_disk* log_u, c3_d len_d)
|
||||
for ( c3_d i_d = 0ULL; i_d < len_d; ++i_d) {
|
||||
c3_assert( (req_u->eve_d + i_d) == tac_u->eve_d );
|
||||
|
||||
req_u->siz_i[i_d] = _disk_serialize_v0(tac_u, &req_u->byt_y[i_d]);
|
||||
req_u->siz_i[i_d] = _disk_serialize_v1(tac_u, &req_u->byt_y[i_d]);
|
||||
|
||||
tac_u = tac_u->nex_u;
|
||||
}
|
||||
@ -276,7 +279,6 @@ u3_disk_boot_plan(u3_disk* log_u, u3_noun job)
|
||||
// NB, boot mugs are 0
|
||||
//
|
||||
u3_fact* tac_u = u3_fact_init(++log_u->sen_d, 0, job);
|
||||
tac_u->bug_l = 0; // XX
|
||||
|
||||
if ( !log_u->put_u.ent_u ) {
|
||||
c3_assert( !log_u->put_u.ext_u );
|
||||
@ -381,9 +383,17 @@ _disk_read_one_cb(void* ptr_v, c3_d eve_d, size_t val_i, void* val_p)
|
||||
u3_disk* log_u = red_u->log_u;
|
||||
u3_fact* tac_u;
|
||||
|
||||
if ( 4 >= val_i ) {
|
||||
return c3n;
|
||||
}
|
||||
|
||||
{
|
||||
u3_noun val, mug, job;
|
||||
c3_l bug_l;
|
||||
u3_noun job;
|
||||
c3_y* dat_y = val_p;
|
||||
c3_l mug_l = dat_y[0]
|
||||
^ (dat_y[1] << 8)
|
||||
^ (dat_y[2] << 16)
|
||||
^ (dat_y[3] << 24);
|
||||
|
||||
#ifdef DISK_TRACE_CUE
|
||||
u3t_event_trace("king disk cue", 'B');
|
||||
@ -391,39 +401,23 @@ _disk_read_one_cb(void* ptr_v, c3_d eve_d, size_t val_i, void* val_p)
|
||||
|
||||
// XX u3m_soft?
|
||||
//
|
||||
val = u3ke_cue(u3i_bytes(val_i, val_p));
|
||||
job = u3ke_cue(u3i_bytes(val_i - 4, dat_y + 4));
|
||||
|
||||
#ifdef DISK_TRACE_CUE
|
||||
u3t_event_trace("king disk cue", 'E');
|
||||
#endif
|
||||
|
||||
if ( (c3n == u3r_cell(val, &mug, &job))
|
||||
|| (c3n == u3r_safe_word(mug, &bug_l)) ) // XX
|
||||
{
|
||||
// failure here triggers cleanup in _disk_read_start_cb()
|
||||
//
|
||||
u3z(val);
|
||||
return c3n;
|
||||
}
|
||||
|
||||
// NB: mug is unknown due to log format
|
||||
//
|
||||
tac_u = u3_fact_init(eve_d, 0, u3k(job));
|
||||
tac_u->bug_l = bug_l;
|
||||
|
||||
u3z(val);
|
||||
tac_u = u3_fact_init(eve_d, mug_l, job);
|
||||
}
|
||||
|
||||
if ( !red_u->ent_u ) {
|
||||
c3_assert( !red_u->ext_u );
|
||||
|
||||
c3_assert( red_u->eve_d == eve_d );
|
||||
// tac_u->mug_l = 0; // XX
|
||||
red_u->ent_u = red_u->ext_u = tac_u;
|
||||
}
|
||||
else {
|
||||
c3_assert( (1ULL + red_u->ent_u->eve_d) == eve_d );
|
||||
// log_u->get_u.ent_u->mug_l = tac_u->bug_l; // XX
|
||||
red_u->ent_u->nex_u = tac_u;
|
||||
red_u->ent_u = tac_u;
|
||||
}
|
||||
@ -488,19 +482,15 @@ u3_disk_read(u3_disk* log_u, c3_d eve_d, c3_d len_d)
|
||||
static c3_o
|
||||
_disk_save_meta(u3_disk* log_u, const c3_c* key_c, u3_atom dat)
|
||||
{
|
||||
u3_atom mat = u3ke_jam(dat);
|
||||
c3_w len_w = u3r_met(3, mat);
|
||||
c3_w len_w = u3r_met(3, dat);
|
||||
c3_y* byt_y = c3_malloc(len_w);
|
||||
c3_o ret_o;
|
||||
u3r_bytes(0, len_w, byt_y, dat);
|
||||
|
||||
u3r_bytes(0, len_w, byt_y, mat);
|
||||
|
||||
ret_o = u3_lmdb_save_meta(log_u->mdb_u, key_c, len_w, byt_y);
|
||||
|
||||
u3z(mat);
|
||||
c3_free(byt_y);
|
||||
|
||||
return ret_o;
|
||||
{
|
||||
c3_o ret_o = u3_lmdb_save_meta(log_u->mdb_u, key_c, len_w, byt_y);
|
||||
c3_free(byt_y);
|
||||
return ret_o;
|
||||
}
|
||||
}
|
||||
|
||||
/* u3_disk_save_meta(): save metadata.
|
||||
@ -513,8 +503,9 @@ u3_disk_save_meta(u3_disk* log_u,
|
||||
{
|
||||
c3_assert( c3y == u3a_is_cat(lif_w) );
|
||||
|
||||
if ( (c3n == _disk_save_meta(log_u, "who", u3i_chubs(2, who_d)))
|
||||
|| (c3n == _disk_save_meta(log_u, "is-fake", fak_o))
|
||||
if ( (c3n == _disk_save_meta(log_u, "version", 1))
|
||||
|| (c3n == _disk_save_meta(log_u, "who", u3i_chubs(2, who_d)))
|
||||
|| (c3n == _disk_save_meta(log_u, "fake", fak_o))
|
||||
|| (c3n == _disk_save_meta(log_u, "life", lif_w)) )
|
||||
{
|
||||
return c3n;
|
||||
@ -540,24 +531,8 @@ _disk_meta_read_cb(void* ptr_v, size_t val_i, void* val_p)
|
||||
static u3_weak
|
||||
_disk_read_meta(u3_disk* log_u, const c3_c* key_c)
|
||||
{
|
||||
u3_weak mat = u3_none;
|
||||
u3_weak dat = u3_none;
|
||||
u3_noun pro;
|
||||
|
||||
u3_lmdb_read_meta(log_u->mdb_u, &mat, key_c, _disk_meta_read_cb);
|
||||
|
||||
if ( u3_none != mat ) {
|
||||
pro = u3m_soft(0, u3ke_cue, mat);
|
||||
|
||||
if ( u3_blip != u3h(pro) ) {
|
||||
fprintf(stderr, "disk: meta cue failed\r\n");
|
||||
}
|
||||
else {
|
||||
dat = u3k(u3t(pro));
|
||||
}
|
||||
}
|
||||
|
||||
u3z(pro);
|
||||
u3_lmdb_read_meta(log_u->mdb_u, &dat, key_c, _disk_meta_read_cb);
|
||||
return dat;
|
||||
}
|
||||
|
||||
@ -569,34 +544,45 @@ u3_disk_read_meta(u3_disk* log_u,
|
||||
c3_o* fak_o,
|
||||
c3_w* lif_w)
|
||||
{
|
||||
u3_weak who = _disk_read_meta(log_u, "who");
|
||||
u3_weak fak = _disk_read_meta(log_u, "is-fake");
|
||||
u3_weak lif = _disk_read_meta(log_u, "life");
|
||||
u3_weak ver, who, fak, lif;
|
||||
|
||||
if ( u3_none == who ) {
|
||||
if ( u3_none == (ver = _disk_read_meta(log_u, "version")) ) {
|
||||
fprintf(stderr, "disk: read meta: no version\r\n");
|
||||
return c3n;
|
||||
}
|
||||
if ( u3_none == (who = _disk_read_meta(log_u, "who")) ) {
|
||||
fprintf(stderr, "disk: read meta: no indentity\r\n");
|
||||
return c3n;
|
||||
}
|
||||
else if ( u3_none == fak ) {
|
||||
if ( u3_none == (fak = _disk_read_meta(log_u, "fake")) ) {
|
||||
fprintf(stderr, "disk: read meta: no fake bit\r\n");
|
||||
u3z(who);
|
||||
return c3n;
|
||||
}
|
||||
else if ( u3_none == lif ) {
|
||||
if ( u3_none == (lif = _disk_read_meta(log_u, "life")) ) {
|
||||
fprintf(stderr, "disk: read meta: no lifecycle length\r\n");
|
||||
u3z(who);
|
||||
return c3n;
|
||||
}
|
||||
|
||||
if ( !((c3y == fak ) || (c3n == fak )) ) {
|
||||
fprintf(stderr, "disk: read meta: invalid fake bit\r\n");
|
||||
u3z(who); u3z(fak); u3z(lif);
|
||||
return c3n;
|
||||
}
|
||||
else if ( c3n == u3a_is_cat(lif) ) {
|
||||
fprintf(stderr, "disk: read meta: invalid lifecycle length\r\n");
|
||||
u3z(who); u3z(fak); u3z(lif);
|
||||
return c3n;
|
||||
{
|
||||
c3_o val_o = c3y;
|
||||
|
||||
if ( 1 != ver ) {
|
||||
fprintf(stderr, "disk: read meta: unknown version %u\r\n", ver);
|
||||
val_o = c3n;
|
||||
}
|
||||
else if ( !((c3y == fak ) || (c3n == fak )) ) {
|
||||
fprintf(stderr, "disk: read meta: invalid fake bit\r\n");
|
||||
val_o = c3n;
|
||||
}
|
||||
else if ( c3n == u3a_is_cat(lif) ) {
|
||||
fprintf(stderr, "disk: read meta: invalid lifecycle length\r\n");
|
||||
val_o = c3n;
|
||||
}
|
||||
|
||||
if ( c3n == val_o ) {
|
||||
u3z(ver); u3z(who); u3z(fak); u3z(lif);
|
||||
return c3n;
|
||||
}
|
||||
}
|
||||
|
||||
if ( who_d ) {
|
||||
|
@ -35,6 +35,7 @@
|
||||
uv_udp_t wax_u; //
|
||||
uv_handle_t had_u; //
|
||||
}; //
|
||||
c3_l sev_l; // instance number
|
||||
ur_cue_test_t* tes_u; // cue-test handle
|
||||
u3_cue_xeno* sil_u; // cue handle
|
||||
c3_c* dns_c; // domain XX multiple/fallback
|
||||
@ -1318,10 +1319,14 @@ _ames_io_talk(u3_auto* car_u)
|
||||
u3_ames* sam_u = (u3_ames*)car_u;
|
||||
_ames_io_start(sam_u);
|
||||
|
||||
// send born event
|
||||
// send born event
|
||||
//
|
||||
{
|
||||
u3_noun wir = u3nt(c3__newt, u3k(u3A->sen), u3_nul);
|
||||
// XX remove [sev_l]
|
||||
//
|
||||
u3_noun wir = u3nt(c3__newt,
|
||||
u3dc("scot", c3__uv, sam_u->sev_l),
|
||||
u3_nul);
|
||||
u3_noun cad = u3nc(c3__born, u3_nul);
|
||||
|
||||
u3_auto_plan(car_u, u3_ovum_init(0, c3__a, wir, cad));
|
||||
@ -1527,5 +1532,15 @@ u3_ames_io_init(u3_pier* pir_u)
|
||||
car_u->io.kick_f = _ames_io_kick;
|
||||
car_u->io.exit_f = _ames_io_exit;
|
||||
|
||||
{
|
||||
u3_noun now;
|
||||
struct timeval tim_u;
|
||||
gettimeofday(&tim_u, 0);
|
||||
|
||||
now = u3_time_in_tv(&tim_u);
|
||||
sam_u->sev_l = u3r_mug(now);
|
||||
u3z(now);
|
||||
}
|
||||
|
||||
return car_u;
|
||||
}
|
||||
|
@ -17,6 +17,7 @@
|
||||
u3_auto car_u; // driver
|
||||
uv_timer_t tim_u; // behn timer
|
||||
c3_o alm_o; // alarm
|
||||
c3_l sev_l; // instance numbers
|
||||
} u3_behn;
|
||||
|
||||
// XX review, move
|
||||
@ -167,9 +168,13 @@ _behn_born_bail(u3_ovum* egg_u, u3_noun lud)
|
||||
static void
|
||||
_behn_io_talk(u3_auto* car_u)
|
||||
{
|
||||
// XX remove u3A->sen
|
||||
u3_behn* teh_u = (u3_behn*)car_u;
|
||||
|
||||
// XX remove [sev_l]
|
||||
//
|
||||
u3_noun wir = u3nt(c3__behn, u3k(u3A->sen), u3_nul);
|
||||
u3_noun wir = u3nt(c3__behn,
|
||||
u3dc("scot", c3__uv, teh_u->sev_l),
|
||||
u3_nul);
|
||||
u3_noun cad = u3nc(c3__born, u3_nul);
|
||||
|
||||
u3_auto_peer(
|
||||
@ -241,5 +246,15 @@ u3_behn_io_init(u3_pier* pir_u)
|
||||
car_u->io.kick_f = _behn_io_kick;
|
||||
car_u->io.exit_f = _behn_io_exit;
|
||||
|
||||
{
|
||||
u3_noun now;
|
||||
struct timeval tim_u;
|
||||
gettimeofday(&tim_u, 0);
|
||||
|
||||
now = u3_time_in_tv(&tim_u);
|
||||
teh_u->sev_l = u3r_mug(now);
|
||||
u3z(now);
|
||||
}
|
||||
|
||||
return car_u;
|
||||
}
|
||||
|
@ -61,6 +61,7 @@
|
||||
*/
|
||||
typedef struct _u3_cttp {
|
||||
u3_auto car_u; // driver
|
||||
c3_l sev_l; // instance number
|
||||
u3_creq* ceq_u; // request list
|
||||
uv_async_t nop_u; // unused handle (async close)
|
||||
h2o_timeout_t tim_u; // request timeout
|
||||
@ -714,14 +715,18 @@ _cttp_creq_quit(u3_creq* ceq_u)
|
||||
static void
|
||||
_cttp_http_client_receive(u3_creq* ceq_u, c3_w sas_w, u3_noun mes, u3_noun uct)
|
||||
{
|
||||
u3_cttp* ctp_u = ceq_u->ctp_u;
|
||||
|
||||
// XX inject partial responses as separate events
|
||||
//
|
||||
u3_noun wir = u3nt(u3i_string("http-client"), u3k(u3A->sen), u3_nul);
|
||||
u3_noun wir = u3nt(u3i_string("http-client"),
|
||||
u3dc("scot", c3__uv, ctp_u->sev_l),
|
||||
u3_nul);
|
||||
u3_noun cad = u3nt(u3i_string("receive"),
|
||||
ceq_u->num_l,
|
||||
u3nq(u3i_string("start"), u3nc(sas_w, mes), uct, c3y));
|
||||
|
||||
u3_auto_plan(&ceq_u->ctp_u->car_u, u3_ovum_init(0, c3__i, wir, cad));
|
||||
u3_auto_plan(&ctp_u->car_u, u3_ovum_init(0, c3__i, wir, cad));
|
||||
}
|
||||
|
||||
/* _cttp_creq_fail(): dispatch error response
|
||||
@ -1011,9 +1016,13 @@ _cttp_ef_http_client(u3_cttp* ctp_u, u3_noun tag, u3_noun dat)
|
||||
static void
|
||||
_cttp_io_talk(u3_auto* car_u)
|
||||
{
|
||||
u3_cttp* ctp_u = (u3_cttp*)car_u;
|
||||
|
||||
// XX remove u3A->sen
|
||||
//
|
||||
u3_noun wir = u3nt(u3i_string("http-client"), u3k(u3A->sen), u3_nul);
|
||||
u3_noun wir = u3nt(u3i_string("http-client"),
|
||||
u3dc("scot", c3__uv, ctp_u->sev_l),
|
||||
u3_nul);
|
||||
u3_noun cad = u3nc(c3__born, u3_nul);
|
||||
|
||||
u3_auto_plan(car_u, u3_ovum_init(0, c3__i, wir, cad));
|
||||
@ -1118,5 +1127,15 @@ u3_cttp_io_init(u3_pier* pir_u)
|
||||
//
|
||||
// car_u->ev.bail_f = ...;
|
||||
|
||||
{
|
||||
u3_noun now;
|
||||
struct timeval tim_u;
|
||||
gettimeofday(&tim_u, 0);
|
||||
|
||||
now = u3_time_in_tv(&tim_u);
|
||||
ctp_u->sev_l = u3r_mug(now);
|
||||
u3z(now);
|
||||
}
|
||||
|
||||
return car_u;
|
||||
}
|
||||
|
@ -98,6 +98,7 @@ typedef struct _u3_h2o_serv {
|
||||
*/
|
||||
typedef struct _u3_httd {
|
||||
u3_auto car_u; // driver
|
||||
c3_l sev_l; // instance number
|
||||
u3_hfig fig_u; // http configuration
|
||||
u3_http* htp_u; // http servers
|
||||
SSL_CTX* tls_u; // server SSL_CTX*
|
||||
@ -1097,9 +1098,7 @@ _http_serv_link(u3_httd* htd_u, u3_http* htp_u)
|
||||
htp_u->sev_l = 1 + htd_u->htp_u->sev_l;
|
||||
}
|
||||
else {
|
||||
// XX load from elsewhere
|
||||
//
|
||||
htp_u->sev_l = u3A->sev_l;
|
||||
htp_u->sev_l = htd_u->sev_l;
|
||||
}
|
||||
|
||||
htp_u->nex_u = htd_u->htp_u;
|
||||
@ -1738,7 +1737,9 @@ _http_serv_start_all(u3_httd* htd_u)
|
||||
|
||||
// XX remove [sen]
|
||||
//
|
||||
u3_noun wir = u3nt(u3i_string("http-server"), u3k(u3A->sen), u3_nul);
|
||||
u3_noun wir = u3nt(u3i_string("http-server"),
|
||||
u3dc("scot", c3__uv, htd_u->sev_l),
|
||||
u3_nul);
|
||||
u3_noun cad = u3nt(c3__live, non, sec);
|
||||
|
||||
u3_auto_plan(&htd_u->car_u, u3_ovum_init(0, c3__e, wir, cad));
|
||||
@ -1848,9 +1849,13 @@ u3_http_ef_form(u3_httd* htd_u, u3_noun fig)
|
||||
static void
|
||||
_http_io_talk(u3_auto* car_u)
|
||||
{
|
||||
// XX remove u3A->sen
|
||||
u3_httd* htd_u = (u3_httd*)car_u;
|
||||
|
||||
// XX remove [sen]
|
||||
//
|
||||
u3_noun wir = u3nt(u3i_string("http-server"), u3k(u3A->sen), u3_nul);
|
||||
u3_noun wir = u3nt(u3i_string("http-server"),
|
||||
u3dc("scot", c3__uv, htd_u->sev_l),
|
||||
u3_nul);
|
||||
u3_noun cad = u3nc(c3__born, u3_nul);
|
||||
|
||||
u3_auto_plan(car_u, u3_ovum_init(0, c3__e, wir, cad));
|
||||
@ -2182,6 +2187,16 @@ u3_http_io_init(u3_pier* pir_u)
|
||||
uv_timer_start(sit_u, _http_seq_heartbeat_cb, HEARTBEAT_TIMEOUT, 0);
|
||||
htd_u->fig_u.sit_u = sit_u;
|
||||
|
||||
{
|
||||
u3_noun now;
|
||||
struct timeval tim_u;
|
||||
gettimeofday(&tim_u, 0);
|
||||
|
||||
now = u3_time_in_tv(&tim_u);
|
||||
htd_u->sev_l = u3r_mug(now);
|
||||
u3z(now);
|
||||
}
|
||||
|
||||
// XX retry up to N?
|
||||
//
|
||||
// car_u->ev.bail_f = ...;
|
||||
|
@ -62,6 +62,7 @@ struct _u3_ufil;
|
||||
*/
|
||||
typedef struct _u3_unix {
|
||||
u3_auto car_u;
|
||||
c3_l sev_l; // instance number
|
||||
u3_umon* mon_u; // mount points
|
||||
c3_c* pax_c; // pier directory
|
||||
c3_o alm; // timer set
|
||||
@ -956,7 +957,9 @@ _unix_update_mount(u3_unix* unx_u, u3_umon* mon_u, u3_noun all)
|
||||
{
|
||||
// XX remove u3A->sen
|
||||
//
|
||||
u3_noun wir = u3nt(c3__sync, u3k(u3A->sen), u3_nul);
|
||||
u3_noun wir = u3nt(c3__sync,
|
||||
u3dc("scot", c3__uv, unx_u->sev_l),
|
||||
u3_nul);
|
||||
u3_noun cad = u3nq(c3__into, u3i_string(mon_u->nam_c), all, can);
|
||||
|
||||
u3_auto_plan(&unx_u->car_u, u3_ovum_init(0, c3__c, wir, cad));
|
||||
@ -1473,5 +1476,15 @@ u3_unix_io_init(u3_pier* pir_u)
|
||||
//
|
||||
// car_u->ev.bail_f = ...l;
|
||||
|
||||
{
|
||||
u3_noun now;
|
||||
struct timeval tim_u;
|
||||
gettimeofday(&tim_u, 0);
|
||||
|
||||
now = u3_time_in_tv(&tim_u);
|
||||
unx_u->sev_l = u3r_mug(now);
|
||||
u3z(now);
|
||||
}
|
||||
|
||||
return car_u;
|
||||
}
|
||||
|
@ -554,10 +554,8 @@ _lord_work_done(u3_lord* god_u,
|
||||
u3_noun act)
|
||||
{
|
||||
u3_fact* tac_u = u3_fact_init(eve_d, mug_l, job);
|
||||
tac_u->bug_l = god_u->mug_l; // XX
|
||||
|
||||
god_u->mug_l = mug_l;
|
||||
god_u->eve_d = eve_d;
|
||||
god_u->mug_l = mug_l;
|
||||
god_u->eve_d = eve_d;
|
||||
|
||||
u3_gift* gif_u = u3_gift_init(eve_d, act);
|
||||
|
||||
|
@ -539,10 +539,6 @@ _pier_work_init(u3_pier* pir_u)
|
||||
|
||||
_pier_work_time(pir_u);
|
||||
|
||||
// for i/o drivers that still use u3A->sen
|
||||
//
|
||||
u3v_numb();
|
||||
|
||||
// XX plan kelvin event
|
||||
//
|
||||
|
||||
@ -785,9 +781,22 @@ static u3_noun
|
||||
_pier_wyrd_card(u3_pier* pir_u)
|
||||
{
|
||||
u3_lord* god_u = pir_u->god_u;
|
||||
u3_noun sen;
|
||||
|
||||
_pier_work_time(pir_u);
|
||||
u3v_numb();
|
||||
|
||||
{
|
||||
c3_l sev_l;
|
||||
u3_noun now;
|
||||
struct timeval tim_u;
|
||||
gettimeofday(&tim_u, 0);
|
||||
|
||||
now = u3_time_in_tv(&tim_u);
|
||||
sev_l = u3r_mug(now);
|
||||
sen = u3dc("scot", c3__uv, sev_l);
|
||||
|
||||
u3z(now);
|
||||
}
|
||||
|
||||
// XX god_u not necessarily available yet, refactor call sites
|
||||
//
|
||||
@ -799,7 +808,7 @@ _pier_wyrd_card(u3_pier* pir_u)
|
||||
u3nc(c3__nock, 4), // god_u->noc_y
|
||||
u3_none);
|
||||
u3_noun wir = u3nc(c3__arvo, u3_nul);
|
||||
return u3nt(c3__wyrd, u3nc(u3k(u3A->sen), ver), kel);
|
||||
return u3nt(c3__wyrd, u3nc(sen, ver), kel);
|
||||
}
|
||||
|
||||
/* _pier_wyrd_init(): send %wyrd.
|
||||
|
@ -1 +1 @@
|
||||
0.10.9-main-post
|
||||
1.0-rc1
|
@ -416,7 +416,7 @@ _serf_sure_core(u3_serf* sef_u, u3_noun cor)
|
||||
|
||||
u3z(u3A->roc);
|
||||
u3A->roc = cor;
|
||||
u3A->ent_d = sef_u->dun_d;
|
||||
u3A->eve_d = sef_u->dun_d;
|
||||
sef_u->mug_l = u3r_mug(u3A->roc);
|
||||
sef_u->mut_o = c3y;
|
||||
}
|
||||
|
Loading…
Reference in New Issue
Block a user