2019-07-21 22:56:18 +03:00
|
|
|
{-# OPTIONS_GHC -Wwarn #-}
|
2019-07-17 02:14:46 +03:00
|
|
|
|
2019-07-21 22:56:18 +03:00
|
|
|
{-
|
2019-07-17 02:14:46 +03:00
|
|
|
- TODO: `recvLen` is not big-endian safe.
|
|
|
|
-}
|
|
|
|
|
2019-08-01 05:34:14 +03:00
|
|
|
module Vere.Serf ( Serf, SerfState(..), doJob
|
2019-07-21 22:56:18 +03:00
|
|
|
, run, shutdown, kill
|
|
|
|
, replay, bootFromSeq, snapshot
|
|
|
|
, collectFX
|
2019-07-22 00:24:07 +03:00
|
|
|
, Config(..), Flags, Flag(..)
|
2019-07-21 22:56:18 +03:00
|
|
|
) where
|
2019-06-01 01:55:21 +03:00
|
|
|
|
2019-07-20 02:18:58 +03:00
|
|
|
import UrbitPrelude hiding (fail)
|
2019-06-01 01:55:21 +03:00
|
|
|
|
2019-07-24 04:34:16 +03:00
|
|
|
import Arvo
|
|
|
|
import Control.Monad.Fail (fail)
|
|
|
|
import Data.Conduit
|
2019-07-12 04:16:40 +03:00
|
|
|
import Data.Void
|
2019-07-02 05:51:26 +03:00
|
|
|
import Noun
|
2019-06-01 01:55:21 +03:00
|
|
|
import System.Process
|
2019-07-12 04:16:40 +03:00
|
|
|
import Vere.Pier.Types
|
2019-06-01 01:55:21 +03:00
|
|
|
|
2019-07-22 00:24:07 +03:00
|
|
|
import Data.Bits (setBit)
|
2019-07-17 02:14:46 +03:00
|
|
|
import Control.Concurrent (threadDelay)
|
2019-07-12 04:16:40 +03:00
|
|
|
import Data.ByteString (hGet)
|
2019-06-18 02:47:20 +03:00
|
|
|
import Data.ByteString.Unsafe (unsafeUseAsCString)
|
2019-07-12 04:16:40 +03:00
|
|
|
import Foreign.Marshal.Alloc (alloca)
|
|
|
|
import Foreign.Ptr (castPtr)
|
2019-07-12 22:24:44 +03:00
|
|
|
import Foreign.Storable (peek, poke)
|
2019-07-21 22:56:18 +03:00
|
|
|
import System.Directory (createDirectoryIfMissing)
|
2019-07-12 04:16:40 +03:00
|
|
|
import System.Exit (ExitCode)
|
2019-06-25 23:58:07 +03:00
|
|
|
|
|
|
|
import qualified Data.ByteString.Unsafe as BS
|
2019-07-17 02:14:46 +03:00
|
|
|
import qualified Data.Text as T
|
2019-07-21 23:30:30 +03:00
|
|
|
import qualified System.IO.Error as IO
|
|
|
|
import qualified System.IO as IO
|
2019-06-25 23:58:07 +03:00
|
|
|
import qualified Urbit.Time as Time
|
2019-07-19 03:52:53 +03:00
|
|
|
import qualified Vere.Log as Log
|
2019-06-18 02:47:20 +03:00
|
|
|
|
|
|
|
|
2019-07-22 00:24:07 +03:00
|
|
|
-- Serf Config -----------------------------------------------------------------
|
|
|
|
|
|
|
|
type Flags = [Flag]
|
|
|
|
|
|
|
|
data Flag
|
|
|
|
= DebugRam
|
|
|
|
| DebugCpu
|
|
|
|
| CheckCorrupt
|
|
|
|
| CheckFatal
|
|
|
|
| Verbose
|
|
|
|
| DryRun
|
|
|
|
| Quiet
|
|
|
|
| Hashless
|
|
|
|
| Trace
|
|
|
|
deriving (Eq, Ord, Show, Enum, Bounded)
|
|
|
|
|
|
|
|
compileFlags :: [Flag] -> Word
|
|
|
|
compileFlags = foldl' (\acc flag -> setBit acc (fromEnum flag)) 0
|
|
|
|
|
|
|
|
data Config = Config FilePath [Flag]
|
2019-07-22 02:33:26 +03:00
|
|
|
deriving (Show)
|
|
|
|
|
2019-08-13 08:56:31 +03:00
|
|
|
debug _msg = pure () -- putStrLn ("[DEBUG]\t" <> msg)
|
2019-07-22 02:33:26 +03:00
|
|
|
|
2019-08-08 01:24:02 +03:00
|
|
|
serf msg = putStrLn ("[SERF]\t" <> msg)
|
2019-07-22 00:24:07 +03:00
|
|
|
|
|
|
|
|
2019-07-17 02:14:46 +03:00
|
|
|
-- Types -----------------------------------------------------------------------
|
2019-06-25 23:58:07 +03:00
|
|
|
|
2019-07-17 08:32:36 +03:00
|
|
|
data SerfState = SerfState
|
|
|
|
{ ssNextEv :: EventId
|
|
|
|
, ssLastMug :: Mug
|
|
|
|
}
|
|
|
|
deriving (Eq, Ord, Show)
|
|
|
|
|
2019-08-15 05:42:48 +03:00
|
|
|
ssLastEv :: SerfState -> EventId
|
|
|
|
ssLastEv = pred . ssNextEv
|
|
|
|
|
2019-06-25 04:10:41 +03:00
|
|
|
data Serf = Serf
|
2019-06-01 01:55:21 +03:00
|
|
|
{ sendHandle :: Handle
|
|
|
|
, recvHandle :: Handle
|
2019-07-21 23:30:30 +03:00
|
|
|
, errThread :: Async ()
|
2019-06-01 01:55:21 +03:00
|
|
|
, process :: ProcessHandle
|
2019-07-17 08:32:36 +03:00
|
|
|
, sState :: MVar SerfState
|
2019-06-01 01:55:21 +03:00
|
|
|
}
|
|
|
|
|
2019-07-21 22:56:18 +03:00
|
|
|
data ShipId = ShipId Ship Bool
|
|
|
|
deriving (Eq, Ord, Show)
|
|
|
|
|
2019-06-25 04:10:41 +03:00
|
|
|
type Play = Maybe (EventId, Mug, ShipId)
|
2019-06-01 01:55:21 +03:00
|
|
|
|
|
|
|
data Plea
|
2019-07-21 04:29:39 +03:00
|
|
|
= PPlay Play
|
|
|
|
| PWork Work
|
2019-07-21 22:56:18 +03:00
|
|
|
| PDone EventId Mug FX
|
2019-07-21 04:29:39 +03:00
|
|
|
| PStdr EventId Cord
|
|
|
|
| PSlog EventId Word32 Tank
|
2019-06-01 03:21:44 +03:00
|
|
|
deriving (Eq, Show)
|
2019-06-01 01:55:21 +03:00
|
|
|
|
2019-07-19 03:52:53 +03:00
|
|
|
type GetJobs = EventId -> Word64 -> IO (Vector Job)
|
2019-06-01 01:55:21 +03:00
|
|
|
|
2019-07-17 08:32:36 +03:00
|
|
|
type ReplacementEv = Job
|
2019-07-21 22:56:18 +03:00
|
|
|
type WorkResult = (SerfState, FX)
|
2019-07-17 08:32:36 +03:00
|
|
|
type SerfResp = Either ReplacementEv WorkResult
|
2019-06-01 03:21:44 +03:00
|
|
|
|
2019-06-25 04:10:41 +03:00
|
|
|
data SerfExn
|
2019-06-01 03:21:44 +03:00
|
|
|
= BadComputeId EventId WorkResult
|
|
|
|
| BadReplacementId EventId ReplacementEv
|
|
|
|
| UnexpectedPlay EventId Play
|
|
|
|
| BadPleaAtom Atom
|
2019-07-20 02:18:58 +03:00
|
|
|
| BadPleaNoun Noun [Text] Text
|
2019-06-18 02:47:20 +03:00
|
|
|
| ReplacedEventDuringReplay EventId ReplacementEv
|
2019-07-16 03:01:45 +03:00
|
|
|
| ReplacedEventDuringBoot EventId ReplacementEv
|
2019-07-21 22:56:18 +03:00
|
|
|
| EffectsDuringBoot EventId FX
|
2019-06-25 04:10:41 +03:00
|
|
|
| SerfConnectionClosed
|
2019-06-19 01:38:24 +03:00
|
|
|
| UnexpectedPleaOnNewShip Plea
|
|
|
|
| InvalidInitialPlea Plea
|
2019-06-01 03:21:44 +03:00
|
|
|
deriving (Show)
|
2019-06-01 01:55:21 +03:00
|
|
|
|
2019-07-17 02:14:46 +03:00
|
|
|
|
|
|
|
-- Instances -------------------------------------------------------------------
|
|
|
|
|
2019-06-25 04:10:41 +03:00
|
|
|
instance Exception SerfExn
|
2019-06-01 03:21:44 +03:00
|
|
|
|
2019-07-21 22:56:18 +03:00
|
|
|
deriveNoun ''ShipId
|
2019-07-17 02:14:46 +03:00
|
|
|
deriveNoun ''Plea
|
|
|
|
|
|
|
|
|
2019-06-01 03:21:44 +03:00
|
|
|
-- Utils -----------------------------------------------------------------------
|
2019-06-01 01:55:21 +03:00
|
|
|
|
|
|
|
printTank :: Word32 -> Tank -> IO ()
|
2019-08-13 01:51:37 +03:00
|
|
|
printTank _pri tank =
|
|
|
|
(serf . unlines . fmap unTape . wash (WashCfg 0 80)) tank
|
2019-06-01 01:55:21 +03:00
|
|
|
|
2019-06-01 03:21:44 +03:00
|
|
|
guardExn :: Exception e => Bool -> e -> IO ()
|
|
|
|
guardExn ok = unless ok . throwIO
|
|
|
|
|
2019-07-12 00:41:09 +03:00
|
|
|
fromRightExn :: Exception e => Either a b -> (a -> e) -> IO b
|
2019-06-25 04:10:41 +03:00
|
|
|
fromRightExn (Left m) exn = throwIO (exn m)
|
|
|
|
fromRightExn (Right x) _ = pure x
|
|
|
|
|
2019-07-17 02:14:46 +03:00
|
|
|
|
|
|
|
-- Process Management ----------------------------------------------------------
|
|
|
|
|
2019-07-22 00:24:07 +03:00
|
|
|
run :: Config -> Acquire Serf
|
|
|
|
run config = mkAcquire (startUp config) tearDown
|
2019-07-21 22:56:18 +03:00
|
|
|
|
2019-07-22 00:24:07 +03:00
|
|
|
startUp :: Config -> IO Serf
|
2019-07-22 02:33:26 +03:00
|
|
|
startUp conf@(Config pierPath flags) = do
|
|
|
|
debug "STARTING SERF"
|
|
|
|
debug (tshow conf)
|
2019-07-21 23:30:30 +03:00
|
|
|
(Just i, Just o, Just e, p) <- createProcess pSpec
|
2019-07-17 08:32:36 +03:00
|
|
|
ss <- newEmptyMVar
|
2019-07-21 23:30:30 +03:00
|
|
|
et <- async (readStdErr e)
|
|
|
|
pure (Serf i o et p ss)
|
2019-07-17 02:14:46 +03:00
|
|
|
where
|
|
|
|
diskKey = ""
|
2019-07-22 00:24:07 +03:00
|
|
|
config = show (compileFlags flags)
|
2019-07-21 23:30:30 +03:00
|
|
|
args = [pierPath, diskKey, config]
|
2019-07-22 03:04:09 +03:00
|
|
|
pSpec = (proc "urbit-worker" args)
|
2019-07-17 02:14:46 +03:00
|
|
|
{ std_in = CreatePipe
|
|
|
|
, std_out = CreatePipe
|
2019-07-21 23:30:30 +03:00
|
|
|
, std_err = CreatePipe
|
2019-07-17 02:14:46 +03:00
|
|
|
}
|
|
|
|
|
2019-07-21 23:30:30 +03:00
|
|
|
readStdErr :: Handle -> IO ()
|
|
|
|
readStdErr h =
|
|
|
|
untilEOFExn $ do
|
|
|
|
ln <- IO.hGetLine h
|
2019-07-22 02:33:26 +03:00
|
|
|
serf ("[stderr] " <> T.strip (pack ln))
|
2019-07-21 23:30:30 +03:00
|
|
|
where
|
2019-07-22 02:33:26 +03:00
|
|
|
eofMsg = "[Serf.readStdErr] serf stderr closed"
|
2019-07-22 00:24:07 +03:00
|
|
|
|
2019-07-21 23:30:30 +03:00
|
|
|
untilEOFExn :: IO () -> IO ()
|
|
|
|
untilEOFExn act = loop
|
|
|
|
where
|
|
|
|
loop = do
|
|
|
|
IO.tryIOError act >>= \case
|
2019-07-22 02:33:26 +03:00
|
|
|
Left exn | IO.isEOFError exn -> do debug eofMsg
|
2019-07-22 00:24:07 +03:00
|
|
|
pure ()
|
2019-07-21 23:30:30 +03:00
|
|
|
Left exn -> IO.ioError exn
|
|
|
|
Right () -> loop
|
|
|
|
|
2019-07-21 22:56:18 +03:00
|
|
|
tearDown :: Serf -> IO ()
|
|
|
|
tearDown serf = do
|
2019-08-13 08:56:31 +03:00
|
|
|
terminateProcess (process serf)
|
|
|
|
void (waitForExit serf)
|
|
|
|
|
|
|
|
-- race_ waitThenKill (shutdownAndWait serf 0)
|
2019-07-22 00:24:07 +03:00
|
|
|
where
|
2019-08-13 08:56:31 +03:00
|
|
|
-- killedMsg =
|
|
|
|
-- "[Serf.tearDown]: Serf didn't die when asked, killing it"
|
2019-07-22 00:24:07 +03:00
|
|
|
|
2019-08-13 08:56:31 +03:00
|
|
|
-- waitThenKill = do
|
|
|
|
-- threadDelay 1000000
|
|
|
|
-- debug killedMsg
|
|
|
|
-- terminateProcess (process serf)
|
2019-07-21 22:56:18 +03:00
|
|
|
|
2019-07-19 03:52:53 +03:00
|
|
|
waitForExit :: Serf -> IO ExitCode
|
|
|
|
waitForExit serf = waitForProcess (process serf)
|
|
|
|
|
2019-07-17 02:14:46 +03:00
|
|
|
kill :: Serf -> IO ExitCode
|
2019-07-19 03:52:53 +03:00
|
|
|
kill serf = terminateProcess (process serf) >> waitForExit serf
|
2019-07-17 02:14:46 +03:00
|
|
|
|
2019-08-13 08:56:31 +03:00
|
|
|
{-
|
2019-07-21 22:56:18 +03:00
|
|
|
shutdownAndWait :: Serf -> Word8 -> IO ExitCode
|
|
|
|
shutdownAndWait serf code = do
|
|
|
|
shutdown serf code
|
|
|
|
waitForExit serf
|
2019-08-13 08:56:31 +03:00
|
|
|
-}
|
2019-07-21 22:56:18 +03:00
|
|
|
|
2019-07-17 02:14:46 +03:00
|
|
|
|
|
|
|
-- Basic Send and Receive Operations -------------------------------------------
|
|
|
|
|
|
|
|
withWord64AsByteString :: Word64 -> (ByteString -> IO a) -> IO a
|
|
|
|
withWord64AsByteString w k = do
|
|
|
|
alloca $ \wp -> do
|
|
|
|
poke wp w
|
|
|
|
bs <- BS.unsafePackCStringLen (castPtr wp, 8)
|
|
|
|
k bs
|
|
|
|
|
|
|
|
sendLen :: Serf -> Int -> IO ()
|
|
|
|
sendLen s i = do
|
|
|
|
w <- evaluate (fromIntegral i :: Word64)
|
|
|
|
withWord64AsByteString (fromIntegral i) (hPut (sendHandle s))
|
|
|
|
|
|
|
|
sendOrder :: Serf -> Order -> IO ()
|
|
|
|
sendOrder w o = do
|
2019-07-22 02:33:26 +03:00
|
|
|
debug ("[Serf.sendOrder.toNoun] " <> tshow o)
|
2019-07-19 03:52:53 +03:00
|
|
|
n <- evaluate (toNoun o)
|
2019-07-21 23:30:30 +03:00
|
|
|
|
|
|
|
case o of
|
2019-08-13 08:56:31 +03:00
|
|
|
OWork (DoWork (Work _ _ _ e)) -> do print (toNoun (e :: Ev))
|
|
|
|
_ -> do pure ()
|
2019-07-21 23:30:30 +03:00
|
|
|
|
2019-07-22 02:33:26 +03:00
|
|
|
debug ("[Serf.sendOrder.jam]")
|
|
|
|
bs <- evaluate (jamBS n)
|
|
|
|
debug ("[Serf.sendOrder.send]: " <> tshow (length bs))
|
|
|
|
sendBytes w bs
|
|
|
|
debug ("[Serf.sendOrder.sent]")
|
2019-07-17 02:14:46 +03:00
|
|
|
|
2019-07-22 02:33:26 +03:00
|
|
|
sendBytes :: Serf -> ByteString -> IO ()
|
2019-08-13 08:56:31 +03:00
|
|
|
sendBytes s bs = handle ioErr $ do
|
2019-07-17 02:14:46 +03:00
|
|
|
sendLen s (length bs)
|
2019-07-22 02:33:26 +03:00
|
|
|
hFlush (sendHandle s)
|
|
|
|
|
2019-08-13 08:56:31 +03:00
|
|
|
hack
|
2019-07-22 02:33:26 +03:00
|
|
|
|
2019-07-17 02:14:46 +03:00
|
|
|
hPut (sendHandle s) bs
|
|
|
|
hFlush (sendHandle s)
|
|
|
|
|
2019-08-13 08:56:31 +03:00
|
|
|
hack
|
|
|
|
|
|
|
|
where
|
|
|
|
ioErr :: IOError -> IO ()
|
|
|
|
ioErr _ = throwIO SerfConnectionClosed
|
|
|
|
|
|
|
|
-- TODO WHY DOES THIS MATTER?????
|
|
|
|
hack = threadDelay 10000
|
2019-07-22 03:04:09 +03:00
|
|
|
|
2019-07-17 02:14:46 +03:00
|
|
|
recvLen :: Serf -> IO Word64
|
|
|
|
recvLen w = do
|
|
|
|
bs <- hGet (recvHandle w) 8
|
|
|
|
case length bs of
|
|
|
|
8 -> unsafeUseAsCString bs (peek . castPtr)
|
|
|
|
_ -> throwIO SerfConnectionClosed
|
|
|
|
|
|
|
|
recvBytes :: Serf -> Word64 -> IO ByteString
|
|
|
|
recvBytes w = do
|
|
|
|
hGet (recvHandle w) . fromIntegral
|
|
|
|
|
|
|
|
recvAtom :: Serf -> IO Atom
|
|
|
|
recvAtom w = do
|
|
|
|
len <- recvLen w
|
|
|
|
bs <- recvBytes w len
|
|
|
|
pure (packAtom bs)
|
|
|
|
where
|
|
|
|
packAtom :: ByteString -> Atom
|
|
|
|
packAtom = view (from atomBytes)
|
|
|
|
|
2019-07-22 02:33:26 +03:00
|
|
|
cordText :: Cord -> Text
|
2019-07-22 21:10:27 +03:00
|
|
|
cordText = T.strip . unCord
|
2019-07-17 02:14:46 +03:00
|
|
|
|
|
|
|
|
2019-06-01 03:21:44 +03:00
|
|
|
--------------------------------------------------------------------------------
|
2019-06-01 01:55:21 +03:00
|
|
|
|
2019-07-21 22:56:18 +03:00
|
|
|
snapshot :: Serf -> SerfState -> IO ()
|
2019-08-15 05:42:48 +03:00
|
|
|
snapshot serf ss = sendOrder serf $ OSave $ ssLastEv ss
|
2019-07-17 02:14:46 +03:00
|
|
|
|
2019-07-21 22:56:18 +03:00
|
|
|
shutdown :: Serf -> Word8 -> IO ()
|
|
|
|
shutdown serf code = sendOrder serf (OExit code)
|
2019-07-17 02:14:46 +03:00
|
|
|
|
|
|
|
{-
|
2019-07-21 04:29:39 +03:00
|
|
|
TODO Find a cleaner way to handle `PStdr` Pleas.
|
2019-07-17 02:14:46 +03:00
|
|
|
-}
|
|
|
|
recvPlea :: Serf -> IO Plea
|
|
|
|
recvPlea w = do
|
2019-07-22 02:33:26 +03:00
|
|
|
debug ("[Vere.Serf.recvPlea] waiting")
|
2019-07-17 02:14:46 +03:00
|
|
|
a <- recvAtom w
|
2019-07-22 02:33:26 +03:00
|
|
|
debug ("[Vere.Serf.recvPlea] got atom")
|
2019-07-17 02:14:46 +03:00
|
|
|
n <- fromRightExn (cue a) (const $ BadPleaAtom a)
|
2019-07-20 02:18:58 +03:00
|
|
|
p <- fromRightExn (fromNounErr n) (\(p,m) -> BadPleaNoun (traceShowId n) p m)
|
2019-07-17 02:14:46 +03:00
|
|
|
|
2019-07-22 02:33:26 +03:00
|
|
|
case p of PStdr e msg -> do serf ("[stdr-plea] " <> cordText msg)
|
2019-07-21 04:29:39 +03:00
|
|
|
recvPlea w
|
|
|
|
PSlog _ pri t -> do printTank pri t
|
|
|
|
recvPlea w
|
2019-07-22 02:33:26 +03:00
|
|
|
_ -> do debug ("[Serf.recvPlea] Got " <> tshow p)
|
2019-07-21 04:29:39 +03:00
|
|
|
pure p
|
2019-07-17 02:14:46 +03:00
|
|
|
|
|
|
|
{-
|
|
|
|
Waits for initial plea, and then sends boot IPC if necessary.
|
|
|
|
-}
|
2019-07-17 08:32:36 +03:00
|
|
|
handshake :: Serf -> LogIdentity -> IO SerfState
|
2019-07-17 02:14:46 +03:00
|
|
|
handshake serf ident = do
|
2019-07-17 08:32:36 +03:00
|
|
|
ss@SerfState{..} <- recvPlea serf >>= \case
|
2019-07-21 04:29:39 +03:00
|
|
|
PPlay Nothing -> pure $ SerfState 1 (Mug 0)
|
|
|
|
PPlay (Just (e, m, _)) -> pure $ SerfState e m
|
|
|
|
x -> throwIO (InvalidInitialPlea x)
|
2019-07-17 02:14:46 +03:00
|
|
|
|
2019-07-17 08:32:36 +03:00
|
|
|
when (ssNextEv == 1) $ do
|
2019-07-17 02:14:46 +03:00
|
|
|
sendOrder serf (OBoot ident)
|
|
|
|
|
2019-07-17 08:32:36 +03:00
|
|
|
pure ss
|
2019-07-17 02:14:46 +03:00
|
|
|
|
2019-07-17 08:32:36 +03:00
|
|
|
sendWork :: Serf -> Job -> IO SerfResp
|
2019-07-21 04:29:39 +03:00
|
|
|
sendWork w job =
|
2019-06-01 01:55:21 +03:00
|
|
|
do
|
2019-07-17 08:32:36 +03:00
|
|
|
sendOrder w (OWork job)
|
2019-06-25 04:10:41 +03:00
|
|
|
res <- loop
|
2019-07-22 02:33:26 +03:00
|
|
|
debug ("[Vere.Serf.sendWork] Got response")
|
2019-06-25 04:10:41 +03:00
|
|
|
pure res
|
2019-06-01 01:55:21 +03:00
|
|
|
where
|
2019-07-21 04:29:39 +03:00
|
|
|
eId = jobId job
|
|
|
|
|
2019-06-25 04:10:41 +03:00
|
|
|
produce :: WorkResult -> IO SerfResp
|
2019-07-17 08:32:36 +03:00
|
|
|
produce (ss@SerfState{..}, o) = do
|
2019-07-21 04:29:39 +03:00
|
|
|
guardExn (ssNextEv == (1+eId)) (BadComputeId eId (ss, o))
|
2019-07-17 08:32:36 +03:00
|
|
|
pure $ Right (ss, o)
|
2019-06-01 03:21:44 +03:00
|
|
|
|
2019-06-25 04:10:41 +03:00
|
|
|
replace :: ReplacementEv -> IO SerfResp
|
2019-07-21 04:29:39 +03:00
|
|
|
replace job = do
|
|
|
|
guardExn (jobId job == eId) (BadReplacementId eId job)
|
2019-07-17 08:32:36 +03:00
|
|
|
pure (Left job)
|
2019-06-01 01:55:21 +03:00
|
|
|
|
2019-06-25 04:10:41 +03:00
|
|
|
loop :: IO SerfResp
|
2019-06-01 03:21:44 +03:00
|
|
|
loop = recvPlea w >>= \case
|
2019-07-21 04:29:39 +03:00
|
|
|
PPlay p -> throwIO (UnexpectedPlay eId p)
|
|
|
|
PDone i m o -> produce (SerfState (i+1) m, o)
|
|
|
|
PWork work -> replace (DoWork work)
|
2019-07-22 02:33:26 +03:00
|
|
|
PStdr _ cord -> serf ("[stdr-plea] " <> cordText cord) >> loop
|
2019-07-21 04:29:39 +03:00
|
|
|
PSlog _ pri t -> printTank pri t >> loop
|
2019-06-01 01:55:21 +03:00
|
|
|
|
2019-07-19 03:52:53 +03:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
2019-07-21 22:56:18 +03:00
|
|
|
doJob :: Serf -> Job -> IO (Job, SerfState, FX)
|
2019-07-21 04:29:39 +03:00
|
|
|
doJob serf job = do
|
2019-07-17 08:32:36 +03:00
|
|
|
sendWork serf job >>= \case
|
|
|
|
Left replaced -> doJob serf replaced
|
|
|
|
Right (ss, fx) -> pure (job, ss, fx)
|
|
|
|
|
|
|
|
bootJob :: Serf -> Job -> IO (Job, SerfState)
|
2019-07-21 04:29:39 +03:00
|
|
|
bootJob serf job = do
|
2019-07-17 08:32:36 +03:00
|
|
|
doJob serf job >>= \case
|
|
|
|
(job, ss, []) -> pure (job, ss)
|
2019-07-21 04:29:39 +03:00
|
|
|
(job, ss, fx) -> throwIO (EffectsDuringBoot (jobId job) fx)
|
2019-07-17 08:32:36 +03:00
|
|
|
|
|
|
|
replayJob :: Serf -> Job -> IO SerfState
|
2019-07-21 04:29:39 +03:00
|
|
|
replayJob serf job = do
|
2019-07-17 08:32:36 +03:00
|
|
|
sendWork serf job >>= \case
|
2019-07-21 22:56:18 +03:00
|
|
|
Left replace -> throwIO (ReplacedEventDuringReplay (jobId job) replace)
|
2019-07-17 08:32:36 +03:00
|
|
|
Right (ss, _) -> pure ss
|
|
|
|
|
2019-07-19 03:52:53 +03:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
2019-07-17 08:32:36 +03:00
|
|
|
type BootSeqFn = EventId -> Mug -> Time.Wen -> Job
|
|
|
|
|
2019-07-21 04:29:39 +03:00
|
|
|
data BootExn = ShipAlreadyBooted
|
|
|
|
deriving stock (Eq, Ord, Show)
|
|
|
|
deriving anyclass (Exception)
|
|
|
|
|
2019-07-17 08:32:36 +03:00
|
|
|
bootFromSeq :: Serf -> BootSeq -> IO ([Job], SerfState)
|
2019-07-16 03:23:48 +03:00
|
|
|
bootFromSeq serf (BootSeq ident nocks ovums) = do
|
|
|
|
handshake serf ident >>= \case
|
2019-07-17 08:32:36 +03:00
|
|
|
ss@(SerfState 1 (Mug 0)) -> loop [] ss bootSeqFns
|
2019-07-21 04:29:39 +03:00
|
|
|
_ -> throwIO ShipAlreadyBooted
|
2019-07-16 03:01:45 +03:00
|
|
|
|
|
|
|
where
|
2019-07-17 08:32:36 +03:00
|
|
|
loop :: [Job] -> SerfState -> [BootSeqFn] -> IO ([Job], SerfState)
|
|
|
|
loop acc ss = \case
|
|
|
|
[] -> pure (reverse acc, ss)
|
|
|
|
x:xs -> do wen <- Time.now
|
|
|
|
job <- pure $ x (ssNextEv ss) (ssLastMug ss) wen
|
|
|
|
(job, ss) <- bootJob serf job
|
|
|
|
loop (job:acc) ss xs
|
|
|
|
|
|
|
|
bootSeqFns :: [BootSeqFn]
|
|
|
|
bootSeqFns = fmap muckNock nocks <> fmap muckOvum ovums
|
2019-07-16 03:23:48 +03:00
|
|
|
where
|
2019-07-21 04:29:39 +03:00
|
|
|
muckNock nok eId mug _ = RunNok $ LifeCyc eId mug nok
|
|
|
|
muckOvum ov eId mug wen = DoWork $ Work eId mug wen ov
|
2019-07-17 02:14:46 +03:00
|
|
|
{-
|
|
|
|
The ship is booted, but it is behind. shove events to the worker
|
|
|
|
until it is caught up.
|
|
|
|
-}
|
2019-07-19 03:52:53 +03:00
|
|
|
replayJobs :: Serf -> SerfState -> ConduitT Job Void IO SerfState
|
|
|
|
replayJobs serf = go
|
|
|
|
where
|
|
|
|
go ss = await >>= maybe (pure ss) (liftIO . replayJob serf >=> go)
|
|
|
|
|
|
|
|
replay :: Serf -> Log.EventLog -> IO SerfState
|
|
|
|
replay serf log = do
|
|
|
|
ss <- handshake serf (Log.identity log)
|
|
|
|
|
|
|
|
runConduit $ Log.streamEvents log (ssNextEv ss)
|
2019-07-21 04:29:39 +03:00
|
|
|
.| toJobs (Log.identity log) (ssNextEv ss)
|
2019-07-19 03:52:53 +03:00
|
|
|
.| replayJobs serf ss
|
|
|
|
|
2019-07-21 22:56:18 +03:00
|
|
|
toJobs :: LogIdentity -> EventId -> ConduitT ByteString Job IO ()
|
2019-07-21 04:29:39 +03:00
|
|
|
toJobs ident eId =
|
2019-07-19 03:52:53 +03:00
|
|
|
await >>= \case
|
2019-07-22 02:33:26 +03:00
|
|
|
Nothing -> putStrLn "[toJobs] no more jobs" >> pure ()
|
2019-07-21 04:29:39 +03:00
|
|
|
Just at -> do yield =<< liftIO (fromAtom at)
|
2019-07-22 02:33:26 +03:00
|
|
|
putStrLn ("[toJobs] " <> tshow eId)
|
2019-07-21 04:29:39 +03:00
|
|
|
toJobs ident (eId+1)
|
2019-06-18 02:47:20 +03:00
|
|
|
where
|
2019-07-21 23:30:30 +03:00
|
|
|
isNock = trace ("[toJobs] " <> show (eId, lifecycleLen ident))
|
2019-07-21 22:56:18 +03:00
|
|
|
$ eId <= fromIntegral (lifecycleLen ident)
|
2019-07-21 04:29:39 +03:00
|
|
|
|
2019-07-21 22:56:18 +03:00
|
|
|
fromAtom :: ByteString -> IO Job
|
|
|
|
fromAtom bs | isNock = do
|
|
|
|
noun <- cueBSExn bs
|
2019-07-21 04:29:39 +03:00
|
|
|
(mug, nok) <- fromNounExn noun
|
|
|
|
pure $ RunNok (LifeCyc eId mug nok)
|
2019-07-21 22:56:18 +03:00
|
|
|
fromAtom bs = do
|
|
|
|
noun <- cueBSExn bs
|
2019-07-21 04:29:39 +03:00
|
|
|
(mug, wen, ovm) <- fromNounExn noun
|
|
|
|
pure $ DoWork (Work eId mug wen ovm)
|
2019-07-19 03:52:53 +03:00
|
|
|
|
|
|
|
|
2019-07-21 22:56:18 +03:00
|
|
|
-- Collect Effects for Parsing -------------------------------------------------
|
|
|
|
|
|
|
|
collectFX :: Serf -> Log.EventLog -> IO ()
|
|
|
|
collectFX serf log = do
|
|
|
|
ss <- handshake serf (Log.identity log)
|
2019-07-17 02:14:46 +03:00
|
|
|
|
2019-07-21 22:56:18 +03:00
|
|
|
runConduit $ Log.streamEvents log (ssNextEv ss)
|
|
|
|
.| toJobs (Log.identity log) (ssNextEv ss)
|
|
|
|
.| doCollectFX serf ss
|
2019-08-21 03:42:53 +03:00
|
|
|
.| persistFX log
|
2019-07-21 22:56:18 +03:00
|
|
|
|
2019-08-21 03:42:53 +03:00
|
|
|
persistFX :: Log.EventLog -> ConduitT (EventId, FX) Void IO ()
|
|
|
|
persistFX log = loop
|
|
|
|
where
|
|
|
|
loop = await >>= \case
|
|
|
|
Nothing -> pure ()
|
|
|
|
Just (eId, fx) -> do
|
|
|
|
liftIO $ Log.writeEffectsRow log eId (jamBS $ toNoun fx)
|
|
|
|
putStr "."
|
|
|
|
loop
|
2019-07-21 22:56:18 +03:00
|
|
|
|
|
|
|
doCollectFX :: Serf -> SerfState -> ConduitT Job (EventId, FX) IO ()
|
|
|
|
doCollectFX serf = go
|
|
|
|
where
|
|
|
|
go :: SerfState -> ConduitT Job (EventId, FX) IO ()
|
|
|
|
go ss = await >>= \case
|
|
|
|
Nothing -> pure ()
|
|
|
|
Just jb -> do
|
2019-08-21 03:42:53 +03:00
|
|
|
-- jb <- pure $ replaceMug jb (ssLastMug ss)
|
2019-07-21 22:56:18 +03:00
|
|
|
(_, ss, fx) <- liftIO (doJob serf jb)
|
|
|
|
liftIO $ print (jobId jb)
|
|
|
|
yield (jobId jb, fx)
|
|
|
|
go ss
|
2019-07-22 03:04:09 +03:00
|
|
|
|
|
|
|
replaceMug :: Job -> Mug -> Job
|
|
|
|
replaceMug jb mug =
|
|
|
|
case jb of
|
|
|
|
DoWork (Work eId _ w o) -> DoWork (Work eId mug w o)
|
|
|
|
RunNok (LifeCyc eId _ n) -> RunNok (LifeCyc eId mug n)
|