support prompt in message serialization

That seems to be the last thing needed for message serialization.
Although it's only used in the assistant currently, so hard to tell if I
forgot something.

At this point, it should be possible to start using transferkeys
when performing transfers, which will allow killing a transferkeys
process if a transfer times out or stalls. But that's for another day.

This commit was sponsored by Ethan Aubin.
This commit is contained in:
Joey Hess 2020-12-04 14:54:09 -04:00
parent 581792bcf0
commit 438d5be1f7
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
8 changed files with 77 additions and 29 deletions

View file

@ -60,7 +60,8 @@ performTransfer :: Transferrer -> Transfer -> TransferInfo -> Assistant Bool
performTransfer transferrer t info = catchBoolIO $ do performTransfer transferrer t info = catchBoolIO $ do
(liftIO $ T.sendRequest t info (transferrerWrite transferrer)) (liftIO $ T.sendRequest t info (transferrerWrite transferrer))
relaySerializedOutput relaySerializedOutput
(liftIO (T.readResponse (transferrerRead transferrer))) (liftIO $ T.readResponse (transferrerRead transferrer))
(liftIO . T.sendSerializedOutputResponse (transferrerWrite transferrer))
liftAnnex liftAnnex
{- Starts a new git-annex transferkeys process, setting up handles {- Starts a new git-annex transferkeys process, setting up handles

View file

@ -41,8 +41,9 @@ start :: CommandStart
start = do start = do
enableInteractiveBranchAccess enableInteractiveBranchAccess
(readh, writeh) <- liftIO dupIoHandles (readh, writeh) <- liftIO dupIoHandles
Annex.setOutput $ SerializedOutput $ Annex.setOutput $ SerializedOutput
hPutStrLn writeh . show . TransferOutput (hPutStrLn writeh . show . TransferOutput)
(readMaybe <$> hGetLine readh)
runRequests readh writeh runner runRequests readh writeh runner
stop stop
where where
@ -101,7 +102,7 @@ runRequests readh writeh a = go Nothing Nothing
hPutStrLn writeh $ show $ TransferResult b hPutStrLn writeh $ show $ TransferResult b
hFlush writeh hFlush writeh
-- FIXME this is bad when used with inAnnex -- | Send a request to this command to perform a transfer.
sendRequest :: Transfer -> TransferInfo -> Handle -> IO () sendRequest :: Transfer -> TransferInfo -> Handle -> IO ()
sendRequest t tinfo h = hPutStrLn h $ show $ TransferRequest sendRequest t tinfo h = hPutStrLn h $ show $ TransferRequest
(transferDirection t) (transferDirection t)
@ -109,6 +110,9 @@ sendRequest t tinfo h = hPutStrLn h $ show $ TransferRequest
(keyData (transferKey t)) (keyData (transferKey t))
(associatedFile tinfo) (associatedFile tinfo)
sendSerializedOutputResponse :: Handle -> SerializedOutputResponse -> IO ()
sendSerializedOutputResponse h sor = hPutStrLn h $ show sor
-- | Read a response from this command. -- | Read a response from this command.
-- --
-- Before the final response, this will return whatever SerializedOutput -- Before the final response, this will return whatever SerializedOutput

View file

@ -288,7 +288,7 @@ commandProgressDisabled = withMessageState $ \s -> return $
NormalOutput -> concurrentOutputEnabled s NormalOutput -> concurrentOutputEnabled s
QuietOutput -> True QuietOutput -> True
JSONOutput _ -> True JSONOutput _ -> True
SerializedOutput _ -> True SerializedOutput _ _ -> True
jsonOutputEnabled :: Annex Bool jsonOutputEnabled :: Annex Bool
jsonOutputEnabled = withMessageState $ \s -> return $ jsonOutputEnabled = withMessageState $ \s -> return $
@ -314,8 +314,20 @@ mkPrompter = getConcurrency >>= \case
where where
goconcurrent = withMessageState $ \s -> do goconcurrent = withMessageState $ \s -> do
let l = promptLock s let l = promptLock s
let (run, cleanup) = case outputType s of
SerializedOutput h hr ->
( \a -> do
liftIO $ outputSerialized h StartPrompt
liftIO $ waitOutputSerializedResponse hr ReadyPrompt
a
, liftIO $ outputSerialized h EndPrompt
)
_ ->
( hideRegionsWhile s
, noop
)
return $ \a -> return $ \a ->
debugLocks $ bracketIO debugLocks $ bracketIO
(takeMVar l) (takeMVar l)
(putMVar l) (\v -> putMVar l v >> cleanup)
(const $ hideRegionsWhile s a) (const $ run a)

View file

@ -29,7 +29,7 @@ outputMessage' jsonoutputter jsonbuilder msg = withMessageState $ \s -> case out
| otherwise -> liftIO $ flushed $ S.putStr msg | otherwise -> liftIO $ flushed $ S.putStr msg
JSONOutput _ -> void $ jsonoutputter jsonbuilder s JSONOutput _ -> void $ jsonoutputter jsonbuilder s
QuietOutput -> q QuietOutput -> q
SerializedOutput h -> do SerializedOutput h _ -> do
liftIO $ outputSerialized h $ OutputMessage msg liftIO $ outputSerialized h $ OutputMessage msg
void $ jsonoutputter jsonbuilder s void $ jsonoutputter jsonbuilder s
@ -37,7 +37,7 @@ outputMessage' jsonoutputter jsonbuilder msg = withMessageState $ \s -> case out
bufferJSON :: JSONBuilder -> MessageState -> Annex Bool bufferJSON :: JSONBuilder -> MessageState -> Annex Bool
bufferJSON jsonbuilder s = case outputType s of bufferJSON jsonbuilder s = case outputType s of
JSONOutput _ -> go (flushed . JSON.emit) JSONOutput _ -> go (flushed . JSON.emit)
SerializedOutput h -> go (outputSerialized h . JSONObject . JSON.encode) SerializedOutput h _ -> go (outputSerialized h . JSONObject . JSON.encode)
_ -> return False _ -> return False
where where
go emitter go emitter
@ -63,7 +63,7 @@ bufferJSON jsonbuilder s = case outputType s of
outputJSON :: JSONBuilder -> MessageState -> Annex Bool outputJSON :: JSONBuilder -> MessageState -> Annex Bool
outputJSON jsonbuilder s = case outputType s of outputJSON jsonbuilder s = case outputType s of
JSONOutput _ -> go (flushed . JSON.emit) JSONOutput _ -> go (flushed . JSON.emit)
SerializedOutput h -> go (outputSerialized h . JSONObject . JSON.encode) SerializedOutput h _ -> go (outputSerialized h . JSONObject . JSON.encode)
_ -> return False _ -> return False
where where
go emitter = do go emitter = do
@ -77,7 +77,7 @@ outputError msg = withMessageState $ \s -> case (outputType s, jsonBuffer s) of
let jb' = Just (JSON.addErrorMessage (lines msg) jb) let jb' = Just (JSON.addErrorMessage (lines msg) jb)
in Annex.changeState $ \st -> in Annex.changeState $ \st ->
st { Annex.output = s { jsonBuffer = jb' } } st { Annex.output = s { jsonBuffer = jb' } }
(SerializedOutput h, _) -> (SerializedOutput h _, _) ->
liftIO $ outputSerialized h $ OutputError msg liftIO $ outputSerialized h $ OutputError msg
_ _
| concurrentOutputEnabled s -> concurrentMessage s True msg go | concurrentOutputEnabled s -> concurrentMessage s True msg go
@ -96,3 +96,9 @@ flushed a = a >> hFlush stdout
outputSerialized :: (SerializedOutput -> IO ()) -> SerializedOutput -> IO () outputSerialized :: (SerializedOutput -> IO ()) -> SerializedOutput -> IO ()
outputSerialized = id outputSerialized = id
-- | Wait for the specified response.
waitOutputSerializedResponse :: (IO (Maybe SerializedOutputResponse)) -> SerializedOutputResponse -> IO ()
waitOutputSerializedResponse getr r = tryIO getr >>= \case
Right (Just r') | r' == r -> return ()
v -> error $ "serialized output protocol error; expected " ++ show r ++ " got " ++ show v

View file

@ -113,7 +113,7 @@ metered' st othermeter msize showoutput a = go st
updateMeter meter updateMeter meter
a meter (combinemeter m) a meter (combinemeter m)
| otherwise = nometer | otherwise = nometer
go (MessageState { outputType = SerializedOutput h }) = do go (MessageState { outputType = SerializedOutput h _ }) = do
liftIO $ outputSerialized h $ StartProgressMeter msize liftIO $ outputSerialized h $ StartProgressMeter msize
meter <- liftIO $ mkMeter msize $ \_ _ _old new -> meter <- liftIO $ mkMeter msize $ \_ _ _old new ->
outputSerialized h $ UpdateProgressMeter $ outputSerialized h $ UpdateProgressMeter $

View file

@ -7,7 +7,11 @@
{-# LANGUAGE RankNTypes #-} {-# LANGUAGE RankNTypes #-}
module Messages.Serialized (outputSerialized, relaySerializedOutput) where module Messages.Serialized (
relaySerializedOutput,
outputSerialized,
waitOutputSerializedResponse,
) where
import Common import Common
import Annex import Annex
@ -19,15 +23,17 @@ import qualified Messages.JSON as JSON
import Control.Monad.IO.Class (MonadIO) import Control.Monad.IO.Class (MonadIO)
-- | Relay serialized output from a child process to the console.
relaySerializedOutput relaySerializedOutput
:: (Monad m, MonadIO m, MonadMask m) :: (Monad m, MonadIO m, MonadMask m)
=> m (Either SerializedOutput r) => m (Either SerializedOutput r)
-- ^ Get next serialized output, or final value to return. -- ^ Get next serialized output, or final value to return.
-> (SerializedOutputResponse -> m ())
-> (forall a. Annex a -> m a) -> (forall a. Annex a -> m a)
-- ^ Run an annex action in the monad. Will not be used with -- ^ Run an annex action in the monad. Will not be used with
-- actions that block for a long time. -- actions that block for a long time.
-> m r -> m r
relaySerializedOutput getso runannex = go Nothing relaySerializedOutput getso sendsor runannex = go Nothing
where where
go st = loop st >>= \case go st = loop st >>= \case
Right r -> return r Right r -> return r
@ -47,7 +53,7 @@ relaySerializedOutput getso runannex = go Nothing
Left (JSONObject b) -> do Left (JSONObject b) -> do
runannex $ withMessageState $ \s -> case outputType s of runannex $ withMessageState $ \s -> case outputType s of
JSONOutput _ -> liftIO $ flushed $ JSON.emit' b JSONOutput _ -> liftIO $ flushed $ JSON.emit' b
SerializedOutput h -> liftIO $ SerializedOutput h _ -> liftIO $
outputSerialized h $ JSONObject b outputSerialized h $ JSONObject b
_ -> q _ -> q
loop st loop st
@ -69,3 +75,18 @@ relaySerializedOutput getso runannex = go Nothing
Just meterupdate -> liftIO $ meterupdate n Just meterupdate -> liftIO $ meterupdate n
Nothing -> noop Nothing -> noop
loop st loop st
Left StartPrompt -> do
prompter <- runannex mkPrompter
v <- prompter $ do
sendsor ReadyPrompt
-- Continue processing serialized output
-- until EndPrompt or a final value is
-- returned. (EndPrompt is all that
-- ought to be sent while in a prompt
-- really, but if something else did get
-- sent, display it just in case.)
loop st
case v of
Right r -> return (Right r)
Left st' -> loop st'
Left EndPrompt -> return (Left st)

View file

@ -20,7 +20,9 @@ data OutputType
= NormalOutput = NormalOutput
| QuietOutput | QuietOutput
| JSONOutput JSONOptions | JSONOutput JSONOptions
| SerializedOutput (SerializedOutput -> IO ()) | SerializedOutput
(SerializedOutput -> IO ())
(IO (Maybe SerializedOutputResponse))
data JSONOptions = JSONOptions data JSONOptions = JSONOptions
{ jsonProgress :: Bool { jsonProgress :: Bool
@ -70,7 +72,13 @@ data SerializedOutput
| StartProgressMeter (Maybe FileSize) | StartProgressMeter (Maybe FileSize)
| UpdateProgressMeter BytesProcessed | UpdateProgressMeter BytesProcessed
| EndProgressMeter | EndProgressMeter
| StartPrompt
| EndPrompt
| JSONObject L.ByteString | JSONObject L.ByteString
-- ^ This is always sent, it's up to the consumer to decide if it -- ^ This is always sent, it's up to the consumer to decide if it
-- wants to display JSON, or human-readable messages. -- wants to display JSON, or human-readable messages.
deriving (Show, Read) deriving (Show, Read)
data SerializedOutputResponse
= ReadyPrompt
deriving (Eq, Show, Read)

View file

@ -25,9 +25,16 @@ A few notes on implementing that:
outputs to stderr directly no matter the output type currently. outputs to stderr directly no matter the output type currently.
It would need to be changed to support the new output type. It would need to be changed to support the new output type.
(And probably should for concurrent output mode too actually!) (And probably should for concurrent output mode too actually!)
> It's true, this is not concurrent output safe. However, that's already
> the case, and output to stderr doesn't affect the piping of serialized
> messages on stdout. So, punted on this.
* So does warningIO, though it's only used in a couple of remotes * So does warningIO, though it's only used in a couple of remotes
and rarely. It would be good to find a way to eliminate it. and rarely. It would be good to find a way to eliminate it.
> Eliminated except for one call in a non-relevant code path.
* Messages.prompt. Which is used by remotes, and would need to * Messages.prompt. Which is used by remotes, and would need to
communicate over the pipe to the parent git-annex bidirectionally. communicate over the pipe to the parent git-annex bidirectionally.
Eg, send a message saying the parent needs to prepare for prompt, Eg, send a message saying the parent needs to prepare for prompt,
@ -35,17 +42,6 @@ A few notes on implementing that:
prompting is done. (Note that the parent would need to detect if the child prompting is done. (Note that the parent would need to detect if the child
process crashed to avoid being locked waiting for the prompt.) process crashed to avoid being locked waiting for the prompt.)
* Messages.Internal.outputMessage is used by several things, and > Done.
includes some special parameters used in json mode. Since the parent
git-annex might itself have json mode enabled, those parameters will need
to be included in the serialization. But those parameters are currently
actually functions that manipulate the json object that will be outputted
later. So cannot be serialized. Uuuuh.
Maybe the thing to do is, pass along the --json options to transferkeys, [[done]]
and have a message type for json objects, which it uses to send them
to git-annex, which can then output them. outputMessage can handle the
new output type by sending the message through the pipe, and also
building any json object, and sending it through the pipe once it's done.
> Started work on this in the message-serialization branch. --[[Joey]]