2019-05-31 00:24:14 +03:00
|
|
|
module Main where
|
|
|
|
|
|
|
|
import ClassyPrelude
|
2019-07-16 03:01:45 +03:00
|
|
|
|
2019-07-24 04:34:16 +03:00
|
|
|
import Arvo
|
|
|
|
import Control.Exception hiding (evaluate)
|
2019-07-19 03:52:53 +03:00
|
|
|
import Data.Acquire
|
|
|
|
import Data.Conduit
|
|
|
|
import Data.Conduit.List
|
2019-07-24 04:34:16 +03:00
|
|
|
import Noun
|
|
|
|
import Vere.Pier
|
|
|
|
import Vere.Pier.Types
|
|
|
|
import Vere.Serf
|
2019-07-16 03:01:45 +03:00
|
|
|
|
2019-07-23 00:46:14 +03:00
|
|
|
import Control.Concurrent (runInBoundThread, threadDelay)
|
|
|
|
import Control.Lens ((&))
|
2019-07-21 07:13:21 +03:00
|
|
|
import System.Directory (doesFileExist, removeFile)
|
2019-07-16 05:20:23 +03:00
|
|
|
import Text.Show.Pretty (pPrint)
|
2019-07-21 07:13:21 +03:00
|
|
|
import Urbit.Time (Wen)
|
2019-06-25 04:10:41 +03:00
|
|
|
|
2019-07-24 04:34:16 +03:00
|
|
|
import qualified Data.Set as Set
|
2019-07-20 06:00:23 +03:00
|
|
|
import qualified Vere.Log as Log
|
|
|
|
import qualified Vere.Pier as Pier
|
2019-07-21 22:56:18 +03:00
|
|
|
import qualified Vere.Serf as Serf
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
zod :: Ship
|
|
|
|
zod = 0
|
2019-06-25 04:10:41 +03:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
2019-05-31 00:24:14 +03:00
|
|
|
|
2019-07-19 03:52:53 +03:00
|
|
|
removeFileIfExists :: FilePath -> IO ()
|
|
|
|
removeFileIfExists pax = do
|
|
|
|
exists <- doesFileExist pax
|
|
|
|
when exists $ do
|
|
|
|
removeFile pax
|
|
|
|
|
2019-07-21 22:56:18 +03:00
|
|
|
catchAny :: IO a -> (SomeException -> IO a) -> IO a
|
|
|
|
catchAny = Control.Exception.catch
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
2019-07-17 08:32:36 +03:00
|
|
|
wipeSnapshot :: FilePath -> IO ()
|
|
|
|
wipeSnapshot shipPath = do
|
2019-07-21 22:56:18 +03:00
|
|
|
removeFileIfExists (shipPath <> "/.urb/chk/north.bin")
|
|
|
|
removeFileIfExists (shipPath <> "/.urb/chk/south.bin")
|
|
|
|
print (shipPath <> "/.urb/chk/north.bin")
|
|
|
|
print (shipPath <> "/.urb/chk/south.bin")
|
2019-06-25 04:10:41 +03:00
|
|
|
|
2019-07-17 08:32:36 +03:00
|
|
|
tryBootFromPill :: FilePath -> FilePath -> Ship -> IO ()
|
|
|
|
tryBootFromPill pillPath shipPath ship = do
|
|
|
|
wipeSnapshot shipPath
|
2019-07-22 02:33:26 +03:00
|
|
|
with (Pier.booted pillPath shipPath serfFlags ship) $ \(serf, log, ss) -> do
|
2019-07-19 03:52:53 +03:00
|
|
|
print "lul"
|
|
|
|
print ss
|
|
|
|
threadDelay 500000
|
2019-07-21 22:56:18 +03:00
|
|
|
shutdown serf 0 >>= print
|
2019-07-21 23:30:30 +03:00
|
|
|
putStrLn "[tryBootFromPill] Booted!"
|
2019-07-16 05:20:23 +03:00
|
|
|
|
2019-07-17 08:32:36 +03:00
|
|
|
tryResume :: FilePath -> IO ()
|
|
|
|
tryResume shipPath = do
|
2019-07-22 02:33:26 +03:00
|
|
|
with (Pier.resumed shipPath serfFlags) $ \(serf, log, ss) -> do
|
2019-07-19 03:52:53 +03:00
|
|
|
print ss
|
|
|
|
threadDelay 500000
|
2019-07-21 22:56:18 +03:00
|
|
|
shutdown serf 0 >>= print
|
2019-07-21 23:30:30 +03:00
|
|
|
putStrLn "[tryResume] Resumed!"
|
2019-06-25 04:10:41 +03:00
|
|
|
|
2019-07-17 08:32:36 +03:00
|
|
|
tryFullReplay :: FilePath -> IO ()
|
|
|
|
tryFullReplay shipPath = do
|
|
|
|
wipeSnapshot shipPath
|
|
|
|
tryResume shipPath
|
|
|
|
|
2019-07-21 22:56:18 +03:00
|
|
|
--------------------------------------------------------------------------------
|
2019-07-20 02:18:58 +03:00
|
|
|
|
|
|
|
tryParseEvents :: FilePath -> EventId -> IO ()
|
|
|
|
tryParseEvents dir first = do
|
|
|
|
vPax <- newIORef []
|
|
|
|
with (Log.existing dir) $ \log -> do
|
|
|
|
let ident = Log.identity log
|
|
|
|
print ident
|
|
|
|
runConduit $ Log.streamEvents log first
|
|
|
|
.| showEvents vPax first (fromIntegral $ lifecycleLen ident)
|
|
|
|
paths <- sort . ordNub <$> readIORef vPax
|
|
|
|
for_ paths print
|
|
|
|
where
|
2019-07-21 22:56:18 +03:00
|
|
|
showEvents :: IORef [Path] -> EventId -> EventId
|
|
|
|
-> ConduitT ByteString Void IO ()
|
2019-07-20 02:18:58 +03:00
|
|
|
showEvents vPax eId cycle = await >>= \case
|
|
|
|
Nothing -> print "Done!"
|
2019-07-21 22:56:18 +03:00
|
|
|
Just bs -> do
|
2019-07-20 02:18:58 +03:00
|
|
|
-- print ("got event", eId)
|
2019-07-21 22:56:18 +03:00
|
|
|
n <- liftIO $ cueBSExn bs
|
2019-07-20 02:18:58 +03:00
|
|
|
-- print ("done cue", eId)
|
2019-07-21 07:13:21 +03:00
|
|
|
when (eId <= cycle) $ do
|
2019-07-21 23:30:30 +03:00
|
|
|
putStrLn ("[tryParseEvents] lifecycle nock: " <> tshow eId)
|
2019-07-21 07:13:21 +03:00
|
|
|
when (eId > cycle) $ liftIO $ do
|
2019-07-24 04:34:16 +03:00
|
|
|
(mug, wen, evNoun) <- unpackJob n
|
|
|
|
case fromNounErr evNoun of
|
2019-07-21 07:13:21 +03:00
|
|
|
Left err -> liftIO $ do
|
|
|
|
-- pPrint err
|
2019-07-24 04:34:16 +03:00
|
|
|
-- pPrint evNoun
|
2019-07-24 07:03:04 +03:00
|
|
|
print err
|
2019-07-24 04:34:16 +03:00
|
|
|
Right (ev :: Ev) -> do
|
2019-07-24 07:03:04 +03:00
|
|
|
-- print ev
|
2019-07-21 07:13:21 +03:00
|
|
|
pure ()
|
2019-07-24 04:34:16 +03:00
|
|
|
-- pPrint ev
|
2019-07-21 07:13:21 +03:00
|
|
|
-- paths <- readIORef vPax
|
2019-07-24 04:34:16 +03:00
|
|
|
-- let pax = case ev of Ovum pax _ -> pax
|
2019-07-21 07:13:21 +03:00
|
|
|
-- writeIORef vPax (pax:paths)
|
|
|
|
-- print ("done from noun", eId)
|
2019-07-24 04:34:16 +03:00
|
|
|
-- print (Job eId mug $ DateOvum date ev)
|
2019-07-21 07:13:21 +03:00
|
|
|
-- unless (eId - first > 1000) $
|
|
|
|
showEvents vPax (succ eId) cycle
|
|
|
|
|
|
|
|
unpackJob :: Noun -> IO (Mug, Wen, Noun)
|
|
|
|
unpackJob n = fromNounExn n
|
2019-07-20 02:18:58 +03:00
|
|
|
|
2019-07-21 22:56:18 +03:00
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
2019-07-22 02:33:26 +03:00
|
|
|
serfFlags :: Serf.Flags
|
|
|
|
serfFlags = [Serf.Hashless, Serf.DryRun] -- [Serf.Verbose, Serf.Trace]
|
|
|
|
|
|
|
|
-- = DebugRam
|
|
|
|
-- | DebugCpu
|
|
|
|
-- | CheckCorrupt
|
|
|
|
-- | CheckFatal
|
|
|
|
-- | Verbose
|
|
|
|
-- | DryRun
|
|
|
|
-- | Quiet
|
|
|
|
-- | Hashless
|
|
|
|
-- | Trace
|
2019-07-22 00:24:07 +03:00
|
|
|
|
2019-07-21 22:56:18 +03:00
|
|
|
collectedFX :: FilePath -> Acquire ()
|
|
|
|
collectedFX top = do
|
|
|
|
log <- Log.existing (top <> "/.urb/log")
|
2019-07-22 02:33:26 +03:00
|
|
|
serf <- Serf.run (Serf.Config top serfFlags)
|
2019-07-21 22:56:18 +03:00
|
|
|
liftIO (Serf.collectFX serf log)
|
|
|
|
|
|
|
|
collectAllFx :: FilePath -> IO ()
|
|
|
|
collectAllFx top = do
|
|
|
|
wipeSnapshot top
|
|
|
|
with (collectedFX top) $ \() ->
|
2019-07-21 23:30:30 +03:00
|
|
|
putStrLn "[collectAllFx] Done collecting effects!"
|
2019-07-21 22:56:18 +03:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
2019-07-17 08:32:36 +03:00
|
|
|
main :: IO ()
|
2019-07-22 03:04:09 +03:00
|
|
|
main = runInBoundThread $ do
|
2019-07-22 02:33:26 +03:00
|
|
|
let pillPath = "/home/benjamin/r/urbit/bin/solid.pill"
|
2019-07-17 08:32:36 +03:00
|
|
|
shipPath = "/home/benjamin/r/urbit/zod/"
|
|
|
|
ship = zod
|
|
|
|
|
2019-07-23 00:26:40 +03:00
|
|
|
-- collectAllFx "/home/benjamin/r/urbit/testnet-zod/"
|
2019-07-21 22:56:18 +03:00
|
|
|
|
2019-07-24 07:03:04 +03:00
|
|
|
tryParseEvents "/home/benjamin/r/urbit/zod/.urb/log" 1
|
|
|
|
tryParseEvents "/home/benjamin/r/urbit/testnet-zod/.urb/log" 1
|
2019-07-23 03:46:06 +03:00
|
|
|
|
2019-07-24 07:03:04 +03:00
|
|
|
tryParseFX "/home/benjamin/zod-fx" 1 100000000
|
|
|
|
tryParseFX "/home/benjamin/testnet-zod-fx" 1 100000000
|
2019-07-17 08:32:36 +03:00
|
|
|
|
2019-07-20 02:18:58 +03:00
|
|
|
-- tryBootFromPill pillPath shipPath ship
|
|
|
|
-- tryResume shipPath
|
|
|
|
-- tryFullReplay shipPath
|
2019-07-17 08:32:36 +03:00
|
|
|
|
2019-07-16 03:01:45 +03:00
|
|
|
pure ()
|
2019-06-25 04:10:41 +03:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
2019-07-23 00:46:14 +03:00
|
|
|
tryParseFX :: FilePath -> Word -> Word -> IO ()
|
|
|
|
tryParseFX pax first last =
|
|
|
|
runConduit $ streamFX pax first last
|
|
|
|
.| tryParseFXStream
|
2019-07-23 00:26:40 +03:00
|
|
|
|
2019-07-23 00:46:14 +03:00
|
|
|
streamFX :: FilePath -> Word -> Word -> ConduitT () ByteString IO ()
|
|
|
|
streamFX dir first last = loop first
|
|
|
|
where
|
|
|
|
loop n = do
|
2019-07-24 04:34:16 +03:00
|
|
|
-- when (n `mod` 1000 == 0) $ do
|
|
|
|
-- print n
|
2019-07-23 00:46:14 +03:00
|
|
|
let fil = dir <> "/" <> show n
|
|
|
|
exists <- liftIO (doesFileExist fil)
|
|
|
|
when (exists && n <= last) $ do
|
|
|
|
liftIO (readFile fil) >>= yield
|
|
|
|
loop (n+1)
|
|
|
|
|
|
|
|
tryParseFXStream :: ConduitT ByteString Void IO ()
|
2019-07-24 04:34:16 +03:00
|
|
|
tryParseFXStream = loop 0 (mempty :: Set (Text, Noun))
|
2019-07-23 03:46:06 +03:00
|
|
|
where
|
2019-07-24 04:34:16 +03:00
|
|
|
loop 1 pax = for_ (setToList pax) print
|
|
|
|
loop errors pax =
|
2019-07-23 03:46:06 +03:00
|
|
|
await >>= \case
|
2019-07-24 04:34:16 +03:00
|
|
|
Nothing -> for_ (setToList pax) $ \(t,n) ->
|
|
|
|
putStrLn (t <> ": " <> tshow n)
|
2019-07-23 03:46:06 +03:00
|
|
|
Just bs -> do
|
|
|
|
n <- liftIO (cueBSExn bs)
|
|
|
|
fromNounErr n & \case
|
2019-07-24 04:34:16 +03:00
|
|
|
Left err -> print err >> loop (errors + 1) pax
|
|
|
|
Right [] -> loop errors pax
|
|
|
|
Right (fx :: FX) -> do
|
|
|
|
-- pax <- pure $ Set.union pax
|
|
|
|
-- $ setFromList
|
|
|
|
-- $ fx <&> \(Effect p v) -> (getTag v, toNoun p)
|
|
|
|
loop errors pax
|
|
|
|
|
|
|
|
-- getTag :: Effect -> Text
|
|
|
|
-- getTag fx =
|
|
|
|
-- let n = toNoun fx
|
|
|
|
-- in case n of
|
|
|
|
-- A _ -> maybe "ERR" unCord (fromNoun n)
|
|
|
|
-- C h _ -> maybe "ERR" unCord (fromNoun h)
|
2019-07-23 00:26:40 +03:00
|
|
|
|
2019-06-25 04:10:41 +03:00
|
|
|
tryCopyLog :: IO ()
|
|
|
|
tryCopyLog = do
|
|
|
|
let logPath = "/Users/erg/src/urbit/zod/.urb/falselog/"
|
2019-05-31 02:04:06 +03:00
|
|
|
falselogPath = "/Users/erg/src/urbit/zod/.urb/falselog2/"
|
2019-05-31 00:24:14 +03:00
|
|
|
|
2019-07-20 06:00:23 +03:00
|
|
|
persistQ <- newTQueueIO
|
|
|
|
releaseQ <- newTQueueIO
|
2019-07-19 03:52:53 +03:00
|
|
|
(ident, nextEv, events) <-
|
2019-07-20 06:00:23 +03:00
|
|
|
with (do { log <- Log.existing logPath
|
|
|
|
; Pier.runPersist log persistQ (writeTQueue releaseQ)
|
|
|
|
; pure log
|
|
|
|
})
|
|
|
|
\log -> do
|
|
|
|
ident <- pure $ Log.identity log
|
|
|
|
events <- runConduit (Log.streamEvents log 1 .| consume)
|
|
|
|
nextEv <- Log.nextEv log
|
2019-07-19 03:52:53 +03:00
|
|
|
pure (ident, nextEv, events)
|
2019-05-31 00:24:14 +03:00
|
|
|
|
2019-06-25 04:10:41 +03:00
|
|
|
print ident
|
2019-07-19 03:52:53 +03:00
|
|
|
print nextEv
|
2019-06-25 04:10:41 +03:00
|
|
|
print (length events)
|
2019-05-31 00:24:14 +03:00
|
|
|
|
2019-07-20 06:00:23 +03:00
|
|
|
persistQ2 <- newTQueueIO
|
|
|
|
releaseQ2 <- newTQueueIO
|
|
|
|
with (do { log <- Log.new falselogPath ident
|
|
|
|
; Pier.runPersist log persistQ2 (writeTQueue releaseQ2)
|
|
|
|
; pure log
|
|
|
|
})
|
|
|
|
$ \log2 -> do
|
2019-07-19 03:52:53 +03:00
|
|
|
let writs = zip [1..] events <&> \(id, a) ->
|
2019-07-21 22:56:18 +03:00
|
|
|
(Writ id Nothing a, [])
|
2019-06-25 04:10:41 +03:00
|
|
|
|
2019-07-19 03:52:53 +03:00
|
|
|
print "About to write"
|
2019-05-31 00:24:14 +03:00
|
|
|
|
2019-07-19 03:52:53 +03:00
|
|
|
for_ writs $ \w ->
|
|
|
|
atomically (writeTQueue persistQ2 w)
|
2019-05-31 00:24:14 +03:00
|
|
|
|
2019-07-19 03:52:53 +03:00
|
|
|
print "About to wait"
|
2019-06-25 04:10:41 +03:00
|
|
|
|
2019-07-19 03:52:53 +03:00
|
|
|
replicateM_ 100 $ do
|
|
|
|
atomically $ readTQueue releaseQ2
|
2019-06-25 04:10:41 +03:00
|
|
|
|
2019-07-19 03:52:53 +03:00
|
|
|
print "Done"
|