mirror of https://github.com/voidlizard/hbs2
Fixed die and SIGINT exit
This commit is contained in:
parent
9fca167dd3
commit
ed7a402fc3
|
@ -124,6 +124,8 @@ import Streaming.Prelude qualified as S
|
||||||
import Graphics.Vty qualified as Vty
|
import Graphics.Vty qualified as Vty
|
||||||
import Graphics.Vty.Platform.Unix qualified as Vty
|
import Graphics.Vty.Platform.Unix qualified as Vty
|
||||||
|
|
||||||
|
import Control.Concurrent.Async (ExceptionInLinkedThread(..))
|
||||||
|
|
||||||
data GoAgainException = GoAgainException
|
data GoAgainException = GoAgainException
|
||||||
deriving (Eq,Ord,Show,Typeable)
|
deriving (Eq,Ord,Show,Typeable)
|
||||||
|
|
||||||
|
@ -668,6 +670,20 @@ respawn opts =
|
||||||
print (self, args)
|
print (self, args)
|
||||||
executeFile self False args Nothing
|
executeFile self False args Nothing
|
||||||
|
|
||||||
|
respawnOnError :: PeerOpts -> IO () -> IO ()
|
||||||
|
respawnOnError opts act =
|
||||||
|
Exception.try act >>= match
|
||||||
|
where match (Right r) = return r
|
||||||
|
match (Left e)
|
||||||
|
| Just (ExceptionInLinkedThread _ e') <- Exception.fromException e = do
|
||||||
|
match (Left e')
|
||||||
|
| Just ec <- Exception.fromException @ExitCode e =
|
||||||
|
notice $ viaShow ec
|
||||||
|
| Just UserInterrupt <- Exception.fromException e =
|
||||||
|
notice "Interrupted by user"
|
||||||
|
| otherwise =
|
||||||
|
myException e >> performGC >> respawn opts
|
||||||
|
|
||||||
runPeer :: forall e s . ( e ~ L4Proto
|
runPeer :: forall e s . ( e ~ L4Proto
|
||||||
, FromStringMaybe (PeerAddr e)
|
, FromStringMaybe (PeerAddr e)
|
||||||
, s ~ Encryption e
|
, s ~ Encryption e
|
||||||
|
@ -676,10 +692,7 @@ runPeer :: forall e s . ( e ~ L4Proto
|
||||||
, HasStorage (PeerM e IO)
|
, HasStorage (PeerM e IO)
|
||||||
)=> PeerOpts -> IO ()
|
)=> PeerOpts -> IO ()
|
||||||
|
|
||||||
runPeer opts = Exception.handle (\e -> myException e
|
runPeer opts = respawnOnError opts $ runResourceT do
|
||||||
>> performGC
|
|
||||||
>> respawn opts
|
|
||||||
) $ runResourceT do
|
|
||||||
|
|
||||||
myself <- liftIO myThreadId
|
myself <- liftIO myThreadId
|
||||||
|
|
||||||
|
@ -1219,8 +1232,8 @@ runPeer opts = Exception.handle (\e -> myException e
|
||||||
rpcProto <- async $ flip runReaderT rpcctx do
|
rpcProto <- async $ flip runReaderT rpcctx do
|
||||||
env <- newNotifyEnvServer @(RefChanEvents L4Proto) refChanNotifySource
|
env <- newNotifyEnvServer @(RefChanEvents L4Proto) refChanNotifySource
|
||||||
envrl <- newNotifyEnvServer @(RefLogEvents L4Proto) refLogNotifySource
|
envrl <- newNotifyEnvServer @(RefLogEvents L4Proto) refLogNotifySource
|
||||||
w1 <- asyncLinked $ runNotifyWorkerServer env
|
w1 <- async $ runNotifyWorkerServer env
|
||||||
w2 <- asyncLinked $ runNotifyWorkerServer envrl
|
w2 <- async $ runNotifyWorkerServer envrl
|
||||||
wws <- replicateM 1 $ async $ runProto @UNIX
|
wws <- replicateM 1 $ async $ runProto @UNIX
|
||||||
[ makeResponse (makeServer @PeerAPI)
|
[ makeResponse (makeServer @PeerAPI)
|
||||||
, makeResponse (makeServer @RefLogAPI)
|
, makeResponse (makeServer @RefLogAPI)
|
||||||
|
@ -1230,7 +1243,7 @@ runPeer opts = Exception.handle (\e -> myException e
|
||||||
, makeResponse (makeNotifyServer @(RefChanEvents L4Proto) env)
|
, makeResponse (makeNotifyServer @(RefChanEvents L4Proto) env)
|
||||||
, makeResponse (makeNotifyServer @(RefLogEvents L4Proto) envrl)
|
, makeResponse (makeNotifyServer @(RefLogEvents L4Proto) envrl)
|
||||||
]
|
]
|
||||||
mapM_ wait (w1 : w2 : wws )
|
void $ waitAnyCancel (w1 : w2 : wws )
|
||||||
|
|
||||||
void $ waitAnyCancel $ w <> [ loop
|
void $ waitAnyCancel $ w <> [ loop
|
||||||
, m1
|
, m1
|
||||||
|
|
|
@ -17,8 +17,7 @@ instance (MonadIO m) => HandleMethod m RpcDie where
|
||||||
handleMethod _ = do
|
handleMethod _ = do
|
||||||
debug $ "rpc.die: exiting"
|
debug $ "rpc.die: exiting"
|
||||||
void $ liftIO $ do
|
void $ liftIO $ do
|
||||||
w <- async $ pause @'Seconds 0.5 >> Exit.exitSuccess
|
pause @'Seconds 0.5 >> Exit.exitSuccess
|
||||||
link w
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
|
@ -24,6 +24,7 @@ import Control.Monad
|
||||||
import Control.Monad.Reader
|
import Control.Monad.Reader
|
||||||
import Data.ByteString ( ByteString )
|
import Data.ByteString ( ByteString )
|
||||||
import UnliftIO
|
import UnliftIO
|
||||||
|
import HBS2.Prelude (asyncLinked)
|
||||||
|
|
||||||
data RPC2Context =
|
data RPC2Context =
|
||||||
RPC2Context
|
RPC2Context
|
||||||
|
@ -49,6 +50,6 @@ instance Monad m => HasOwnPeer UNIX (ReaderT RPC2Context m) where
|
||||||
|
|
||||||
instance (MonadUnliftIO m, HasProtocol UNIX (ServiceProto (api :: [Type]) UNIX))
|
instance (MonadUnliftIO m, HasProtocol UNIX (ServiceProto (api :: [Type]) UNIX))
|
||||||
=> HasDeferred (ServiceProto api UNIX) UNIX m where
|
=> HasDeferred (ServiceProto api UNIX) UNIX m where
|
||||||
deferred m = void $ async m
|
deferred m = void $ asyncLinked m
|
||||||
|
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue