From 2c234cb9b286c4504fd534f897293e26b3e93f92 Mon Sep 17 00:00:00 2001 From: Chris Penner Date: Tue, 28 Jan 2025 15:27:46 -0800 Subject: [PATCH 1/8] Add API and implementation for negotiating which causals to sync --- unison-cli/src/Unison/Share/SyncV2.hs | 68 ++++++++++++++++++--- unison-share-api/src/Unison/SyncV2/API.hs | 8 ++- unison-share-api/src/Unison/SyncV2/Types.hs | 58 ++++++++++++++++++ 3 files changed, 126 insertions(+), 8 deletions(-) diff --git a/unison-cli/src/Unison/Share/SyncV2.hs b/unison-cli/src/Unison/Share/SyncV2.hs index ec65a4ca13..8f297d2bea 100644 --- a/unison-cli/src/Unison/Share/SyncV2.hs +++ b/unison-cli/src/Unison/Share/SyncV2.hs @@ -22,7 +22,8 @@ import Data.Attoparsec.ByteString.Char8 qualified as A8 import Data.ByteString qualified as BS import Data.ByteString.Lazy qualified as BL import Data.Conduit.Attoparsec qualified as C -import Data.Conduit.List qualified as C +import Data.Conduit.Combinators qualified as C +import Data.Conduit.List qualified as CL import Data.Conduit.Zlib qualified as C import Data.Foldable qualified as Foldable import Data.Graph qualified as Graph @@ -148,13 +149,13 @@ syncFromCodeserver :: SyncV2.BranchRef -> -- | The hash to download. Share.HashJWT -> - Set Hash32 -> -- | Callback that's given a number of entities we just downloaded. (Int -> IO ()) -> Cli (Either (SyncError SyncV2.PullError) ()) -syncFromCodeserver shouldValidate unisonShareUrl branchRef hashJwt knownHashes _downloadedCallback = do +syncFromCodeserver shouldValidate unisonShareUrl branchRef hashJwt _downloadedCallback = do Cli.Env {authHTTPClient, codebase} <- ask runExceptT do + knownHashes <- ExceptT $ negotiateKnownCausals unisonShareUrl branchRef hashJwt let hash = Share.hashJWTHash hashJwt ExceptT $ do (Cli.runTransaction (Q.entityLocation hash)) >>= \case @@ -247,7 +248,7 @@ syncSortedStream shouldValidate codebase stream = do validateAndSave shouldValidate codebase entityBatch C.runConduit $ stream - C..| C.chunksOf batchSize + C..| CL.chunksOf batchSize C..| unpackChunks codebase C..| handler @@ -441,13 +442,15 @@ syncAPI :: Proxy SyncAPI syncAPI = Proxy @SyncAPI downloadEntitiesStreamClientM :: SyncV2.DownloadEntitiesRequest -> Servant.ClientM (Servant.SourceT IO (CBORStream SyncV2.DownloadEntitiesChunk)) +causalDependenciesStreamClientM :: SyncV2.CausalDependenciesRequest -> Servant.ClientM (Servant.SourceT IO (CBORStream SyncV2.CausalDependenciesChunk)) SyncV2.Routes - { downloadEntitiesStream = downloadEntitiesStreamClientM + { downloadEntitiesStream = downloadEntitiesStreamClientM, + causalDependenciesStream = causalDependenciesStreamClientM } = Servant.client syncAPI -- | Helper for running clientM that returns a stream of entities. -- You MUST consume the stream within the callback, it will be closed when the callback returns. -withConduit :: forall r. Servant.ClientEnv -> (Stream () (SyncV2.DownloadEntitiesChunk) -> StreamM r) -> Servant.ClientM (Servant.SourceIO (CBORStream SyncV2.DownloadEntitiesChunk)) -> StreamM r +withConduit :: forall r chunk. Servant.ClientEnv -> (Stream () chunk -> StreamM r) -> Servant.ClientM (Servant.SourceIO (CBORStream chunk)) -> StreamM r withConduit clientEnv callback clientM = do ExceptT $ withRunInIO \runInIO -> do Servant.withClientM clientM clientEnv $ \case @@ -480,7 +483,6 @@ handleClientError clientEnv err = -- | Stream entities from the codeserver. httpStreamEntities :: - forall. Auth.AuthenticatedHttpClient -> Servant.BaseUrl -> SyncV2.DownloadEntitiesRequest -> @@ -522,6 +524,58 @@ initializeStream stream = do SyncV2.ErrorC (SyncV2.ErrorChunk err) -> throwError . SyncError $ SyncV2.PullError'DownloadEntities err SyncV2.InitialC {} -> throwError . SyncError $ SyncV2.PullError'Sync SyncV2.SyncErrorMisplacedInitialChunk +------------------------------------------------------------------------------------------------------------------------ +-- Causal Dependency negotiation +------------------------------------------------------------------------------------------------------------------------ + +httpStreamCausalDependencies :: + forall r. + Auth.AuthenticatedHttpClient -> + Servant.BaseUrl -> + SyncV2.CausalDependenciesRequest -> + (Stream () SyncV2.CausalDependenciesChunk -> StreamM r) -> + StreamM r +httpStreamCausalDependencies (Auth.AuthenticatedHttpClient httpClient) unisonShareUrl req callback = do + let clientEnv = + (Servant.mkClientEnv httpClient unisonShareUrl) + { Servant.makeClientRequest = \url request -> + -- Disable client-side timeouts + (Servant.defaultMakeClientRequest url request) + <&> \r -> + r + { Http.Client.responseTimeout = Http.Client.responseTimeoutNone + } + } + (causalDependenciesStreamClientM req) & withConduit clientEnv callback + +-- | Ask Share for the dependencies of a given hash jwt, +-- then filter them to get the set of causals which we have and don't need sent. +negotiateKnownCausals :: + -- | The Unison Share URL. + Servant.BaseUrl -> + -- | The branch to download from. + SyncV2.BranchRef -> + -- | The hash to download. + Share.HashJWT -> + Cli (Either (SyncError SyncV2.PullError) (Set Hash32)) +negotiateKnownCausals unisonShareUrl branchRef hashJwt = do + Cli.Env {authHTTPClient, codebase} <- ask + Timing.time "Causal Negotiation" $ do + liftIO . C.runResourceT . runExceptT $ httpStreamCausalDependencies + authHTTPClient + unisonShareUrl + SyncV2.CausalDependenciesRequest {branchRef, rootCausal = hashJwt} + \stream -> do + Set.fromList <$> C.runConduit (stream C..| C.map unpack C..| C.filterM (haveCausalHash codebase) C..| C.sinkList) + where + unpack :: SyncV2.CausalDependenciesChunk -> Hash32 + unpack = \case + SyncV2.HashC causalHash -> causalHash + haveCausalHash :: Codebase.Codebase IO v a -> Hash32 -> StreamM Bool + haveCausalHash codebase causalHash = do + liftIO $ Codebase.runTransaction codebase do + Q.causalExistsByHash32 causalHash + ------------------------------------------------------------------------------------------------------------------------ -- Progress Tracking ------------------------------------------------------------------------------------------------------------------------ diff --git a/unison-share-api/src/Unison/SyncV2/API.hs b/unison-share-api/src/Unison/SyncV2/API.hs index 4aec0e6b54..b4ed916475 100644 --- a/unison-share-api/src/Unison/SyncV2/API.hs +++ b/unison-share-api/src/Unison/SyncV2/API.hs @@ -23,7 +23,13 @@ type DownloadEntitiesStream = ReqBody '[CBOR, JSON] DownloadEntitiesRequest :> StreamPost NoFraming OctetStream (SourceIO (CBORStream DownloadEntitiesChunk)) +-- | Get the relevant dependencies of a causal, including the causal spine and the causal hashes of any library roots. +type CausalDependenciesStream = + ReqBody '[CBOR, JSON] CausalDependenciesRequest + :> StreamPost NetstringFraming CBOR (SourceIO CausalDependenciesChunk) + data Routes mode = Routes - { downloadEntitiesStream :: mode :- "entities" :> "download" :> DownloadEntitiesStream + { downloadEntitiesStream :: mode :- "entities" :> "download" :> DownloadEntitiesStream, + causalDependenciesStream :: mode :- "entities" :> "dependencies" :> CausalDependenciesStream } deriving stock (Generic) diff --git a/unison-share-api/src/Unison/SyncV2/Types.hs b/unison-share-api/src/Unison/SyncV2/Types.hs index c2935110d9..9868b9c441 100644 --- a/unison-share-api/src/Unison/SyncV2/Types.hs +++ b/unison-share-api/src/Unison/SyncV2/Types.hs @@ -1,3 +1,5 @@ +{-# LANGUAGE RecordWildCards #-} + module Unison.SyncV2.Types ( DownloadEntitiesRequest (..), DownloadEntitiesChunk (..), @@ -6,6 +8,8 @@ module Unison.SyncV2.Types StreamInitInfo (..), SyncError (..), DownloadEntitiesError (..), + CausalDependenciesRequest (..), + CausalDependenciesChunk (..), CBORBytes (..), CBORStream(..), EntityKind (..), @@ -24,6 +28,7 @@ import Codec.Serialise qualified as CBOR import Codec.Serialise.Decoding qualified as CBOR import Control.Exception (Exception) import Data.Aeson (FromJSON (..), ToJSON (..), object, withObject, (.:), (.=)) +import Data.Aeson qualified as Aeson import Data.Map (Map) import Data.Map qualified as Map import Data.Set (Set) @@ -299,3 +304,56 @@ instance Serialise EntityKind where 3 -> pure TypeEntity 4 -> pure PatchEntity _ -> fail "invalid tag" + +------------------------------------------------------------------------------------------------------------------------ +-- Causal Dependencies + +data CausalDependenciesRequest = CausalDependenciesRequest + { branchRef :: BranchRef, + rootCausal :: HashJWT + } + deriving stock (Show, Eq, Ord) + +instance ToJSON CausalDependenciesRequest where + toJSON (CausalDependenciesRequest branchRef rootCausal) = + object + [ "branch_ref" .= branchRef, + "root_causal" .= rootCausal + ] + +instance FromJSON CausalDependenciesRequest where + parseJSON = Aeson.withObject "CausalDependenciesRequest" \obj -> do + branchRef <- obj .: "branch_ref" + rootCausal <- obj .: "root_causal" + pure CausalDependenciesRequest {..} + +instance Serialise CausalDependenciesRequest where + encode (CausalDependenciesRequest {branchRef, rootCausal}) = + encode branchRef <> encode rootCausal + decode = CausalDependenciesRequest <$> decode <*> decode + +-- | A chunk of the download entities response stream. +data CausalDependenciesChunk + = HashC Hash32 + deriving (Show, Eq, Ord) + +data CausalDependenciesChunkTag = HashChunkTag + deriving (Show, Eq, Ord) + +instance Serialise CausalDependenciesChunkTag where + encode = \case + HashChunkTag -> CBOR.encodeWord8 0 + decode = do + tag <- CBOR.decodeWord8 + case tag of + 0 -> pure HashChunkTag + _ -> fail "invalid tag" + +instance Serialise CausalDependenciesChunk where + encode = \case + (HashC ch) -> do + encode HashChunkTag <> CBOR.encode ch + decode = do + tag <- decode + case tag of + HashChunkTag -> HashC <$> CBOR.decode From 32aae20f59c09ff21aa2484b9440384bd8accc53 Mon Sep 17 00:00:00 2001 From: Chris Penner Date: Thu, 30 Jan 2025 11:43:54 -0800 Subject: [PATCH 2/8] Get building --- unison-cli/src/Unison/Cli/DownloadUtils.hs | 5 +---- unison-cli/src/Unison/Share/SyncV2.hs | 2 +- 2 files changed, 2 insertions(+), 5 deletions(-) diff --git a/unison-cli/src/Unison/Cli/DownloadUtils.hs b/unison-cli/src/Unison/Cli/DownloadUtils.hs index 5cae49f49c..68c21dc6a2 100644 --- a/unison-cli/src/Unison/Cli/DownloadUtils.hs +++ b/unison-cli/src/Unison/Cli/DownloadUtils.hs @@ -11,7 +11,6 @@ where import Control.Concurrent.STM (atomically) import Control.Concurrent.STM.TVar (modifyTVar', newTVarIO, readTVar, readTVarIO) import Data.List.NonEmpty (pattern (:|)) -import Data.Set qualified as Set import System.Console.Regions qualified as Console.Regions import U.Codebase.HashTags (CausalHash) import U.Codebase.Sqlite.Queries qualified as Queries @@ -67,11 +66,9 @@ downloadProjectBranchFromShare syncVersion useSquashed branch = Cli.respond (Output.DownloadedEntities numDownloaded) SyncV2 -> do let branchRef = SyncV2.BranchRef (into @Text (ProjectAndBranch branch.projectName remoteProjectBranchName)) - -- TODO: Fill this in. - let knownHashes = Set.empty let downloadedCallback = \_ -> pure () let shouldValidate = not $ Codeserver.isCustomCodeserver Codeserver.defaultCodeserver - result <- SyncV2.syncFromCodeserver shouldValidate Share.hardCodedBaseUrl branchRef causalHashJwt knownHashes downloadedCallback + result <- SyncV2.syncFromCodeserver shouldValidate Share.hardCodedBaseUrl branchRef causalHashJwt downloadedCallback result & onLeft \err0 -> do done case err0 of Share.SyncError pullErr -> diff --git a/unison-cli/src/Unison/Share/SyncV2.hs b/unison-cli/src/Unison/Share/SyncV2.hs index 8f297d2bea..5c6fdba7c7 100644 --- a/unison-cli/src/Unison/Share/SyncV2.hs +++ b/unison-cli/src/Unison/Share/SyncV2.hs @@ -219,7 +219,7 @@ syncUnsortedStream shouldValidate codebase stream = do allEntities <- C.runConduit $ stream - C..| C.chunksOf batchSize + C..| CL.chunksOf batchSize C..| unpackChunks codebase C..| validateBatch C..| C.concat From 3e7f26342cd9e9776a1c746d42c5b2d47591956c Mon Sep 17 00:00:00 2001 From: Chris Penner Date: Fri, 31 Jan 2025 13:56:27 -0800 Subject: [PATCH 3/8] Switch causal dependency stream to CBORStream --- unison-cli/src/Unison/Share/SyncV2.hs | 12 +++--- unison-share-api/src/Unison/SyncV2/API.hs | 2 +- unison-share-api/src/Unison/SyncV2/Types.hs | 45 +++++++++++++++++---- 3 files changed, 44 insertions(+), 15 deletions(-) diff --git a/unison-cli/src/Unison/Share/SyncV2.hs b/unison-cli/src/Unison/Share/SyncV2.hs index 5c6fdba7c7..4eda9ac8d9 100644 --- a/unison-cli/src/Unison/Share/SyncV2.hs +++ b/unison-cli/src/Unison/Share/SyncV2.hs @@ -386,7 +386,7 @@ _decodeFramedEntity bs = do Right chunk -> pure chunk -- | Unpacks a stream of tightly-packed CBOR entities without any framing/separators. -decodeUnframedEntities :: Stream ByteString SyncV2.DownloadEntitiesChunk +decodeUnframedEntities :: forall a. (CBOR.Serialise a) => Stream ByteString a decodeUnframedEntities = C.transPipe (mapExceptT (lift . stToIO)) $ do C.await >>= \case Nothing -> pure () @@ -394,13 +394,13 @@ decodeUnframedEntities = C.transPipe (mapExceptT (lift . stToIO)) $ do d <- newDecoder loop bs d where - newDecoder :: ConduitT ByteString SyncV2.DownloadEntitiesChunk (ExceptT SyncErr (ST s)) (Maybe ByteString -> ST s (CBOR.IDecode s (SyncV2.DownloadEntitiesChunk))) + newDecoder :: ConduitT ByteString a (ExceptT SyncErr (ST s)) (Maybe ByteString -> ST s (CBOR.IDecode s a)) newDecoder = do (lift . lift) CBOR.deserialiseIncremental >>= \case CBOR.Done _ _ _ -> throwError . SyncError . SyncV2.PullError'Sync $ SyncV2.SyncErrorStreamFailure "Invalid initial decoder" CBOR.Fail _ _ err -> throwError . SyncError . SyncV2.PullError'Sync $ SyncV2.SyncErrorDeserializationFailure err CBOR.Partial k -> pure k - loop :: ByteString -> (Maybe ByteString -> ST s (CBOR.IDecode s (SyncV2.DownloadEntitiesChunk))) -> ConduitT ByteString SyncV2.DownloadEntitiesChunk (ExceptT SyncErr (ST s)) () + loop :: ByteString -> (Maybe ByteString -> ST s (CBOR.IDecode s a)) -> ConduitT ByteString a (ExceptT SyncErr (ST s)) () loop bs k = do (lift . lift) (k (Just bs)) >>= \case CBOR.Fail _ _ err -> throwError . SyncError . SyncV2.PullError'Sync $ SyncV2.SyncErrorDeserializationFailure err @@ -450,7 +450,7 @@ SyncV2.Routes -- | Helper for running clientM that returns a stream of entities. -- You MUST consume the stream within the callback, it will be closed when the callback returns. -withConduit :: forall r chunk. Servant.ClientEnv -> (Stream () chunk -> StreamM r) -> Servant.ClientM (Servant.SourceIO (CBORStream chunk)) -> StreamM r +withConduit :: forall r chunk. (CBOR.Serialise chunk) => Servant.ClientEnv -> (Stream () chunk -> StreamM r) -> Servant.ClientM (Servant.SourceIO (CBORStream chunk)) -> StreamM r withConduit clientEnv callback clientM = do ExceptT $ withRunInIO \runInIO -> do Servant.withClientM clientM clientEnv $ \case @@ -459,7 +459,7 @@ withConduit clientEnv callback clientM = do conduit <- liftIO $ Servant.fromSourceIO sourceT (runInIO . runExceptT $ callback (conduit C..| unpackCBORBytesStream)) -unpackCBORBytesStream :: Stream (CBORStream SyncV2.DownloadEntitiesChunk) SyncV2.DownloadEntitiesChunk +unpackCBORBytesStream :: (CBOR.Serialise a) => Stream (CBORStream a) a unpackCBORBytesStream = C.map (BL.toStrict . coerce @_ @BL.ByteString) C..| decodeUnframedEntities @@ -570,7 +570,7 @@ negotiateKnownCausals unisonShareUrl branchRef hashJwt = do where unpack :: SyncV2.CausalDependenciesChunk -> Hash32 unpack = \case - SyncV2.HashC causalHash -> causalHash + SyncV2.CausalHashDepC {causalHash} -> causalHash haveCausalHash :: Codebase.Codebase IO v a -> Hash32 -> StreamM Bool haveCausalHash codebase causalHash = do liftIO $ Codebase.runTransaction codebase do diff --git a/unison-share-api/src/Unison/SyncV2/API.hs b/unison-share-api/src/Unison/SyncV2/API.hs index b4ed916475..ef80d3d1cf 100644 --- a/unison-share-api/src/Unison/SyncV2/API.hs +++ b/unison-share-api/src/Unison/SyncV2/API.hs @@ -26,7 +26,7 @@ type DownloadEntitiesStream = -- | Get the relevant dependencies of a causal, including the causal spine and the causal hashes of any library roots. type CausalDependenciesStream = ReqBody '[CBOR, JSON] CausalDependenciesRequest - :> StreamPost NetstringFraming CBOR (SourceIO CausalDependenciesChunk) + :> StreamPost NoFraming OctetStream (SourceIO (CBORStream CausalDependenciesChunk)) data Routes mode = Routes { downloadEntitiesStream :: mode :- "entities" :> "download" :> DownloadEntitiesStream, diff --git a/unison-share-api/src/Unison/SyncV2/Types.hs b/unison-share-api/src/Unison/SyncV2/Types.hs index 9868b9c441..52f6c543b8 100644 --- a/unison-share-api/src/Unison/SyncV2/Types.hs +++ b/unison-share-api/src/Unison/SyncV2/Types.hs @@ -11,7 +11,7 @@ module Unison.SyncV2.Types CausalDependenciesRequest (..), CausalDependenciesChunk (..), CBORBytes (..), - CBORStream(..), + CBORStream (..), EntityKind (..), serialiseCBORBytes, deserialiseOrFailCBORBytes, @@ -332,28 +332,57 @@ instance Serialise CausalDependenciesRequest where encode branchRef <> encode rootCausal decode = CausalDependenciesRequest <$> decode <*> decode +data DependencyType + = -- This is a top-level history node of the root we're pulling. + CausalSpineDependency + | -- This is the causal root of a library dependency. + LibDependency + deriving (Show, Eq, Ord) + +instance Serialise DependencyType where + encode = \case + CausalSpineDependency -> CBOR.encodeWord8 0 + LibDependency -> CBOR.encodeWord8 1 + decode = do + tag <- CBOR.decodeWord8 + case tag of + 0 -> pure CausalSpineDependency + 1 -> pure LibDependency + _ -> fail "invalid tag" + +instance ToJSON DependencyType where + toJSON = \case + CausalSpineDependency -> "causal_spine" + LibDependency -> "lib" + +instance FromJSON DependencyType where + parseJSON = Aeson.withText "DependencyType" \case + "causal_spine" -> pure CausalSpineDependency + "lib" -> pure LibDependency + _ -> fail "invalid DependencyType" + -- | A chunk of the download entities response stream. data CausalDependenciesChunk - = HashC Hash32 + = CausalHashDepC {causalHash :: Hash32, dependencyType :: DependencyType} deriving (Show, Eq, Ord) -data CausalDependenciesChunkTag = HashChunkTag +data CausalDependenciesChunkTag = CausalHashDepChunkTag deriving (Show, Eq, Ord) instance Serialise CausalDependenciesChunkTag where encode = \case - HashChunkTag -> CBOR.encodeWord8 0 + CausalHashDepChunkTag -> CBOR.encodeWord8 0 decode = do tag <- CBOR.decodeWord8 case tag of - 0 -> pure HashChunkTag + 0 -> pure CausalHashDepChunkTag _ -> fail "invalid tag" instance Serialise CausalDependenciesChunk where encode = \case - (HashC ch) -> do - encode HashChunkTag <> CBOR.encode ch + (CausalHashDepC {causalHash, dependencyType}) -> do + encode CausalHashDepChunkTag <> CBOR.encode causalHash <> CBOR.encode dependencyType decode = do tag <- decode case tag of - HashChunkTag -> HashC <$> CBOR.decode + CausalHashDepChunkTag -> CausalHashDepC <$> CBOR.decode <*> CBOR.decode From 3e6720928859b73792d3872b3257ecb9c55d7f11 Mon Sep 17 00:00:00 2001 From: Chris Penner Date: Fri, 31 Jan 2025 16:14:22 -0800 Subject: [PATCH 4/8] Take dependencies till we know enough, then hang up. --- unison-cli/src/Unison/Share/SyncV2.hs | 30 ++++++++++++++++++--- unison-share-api/src/Unison/SyncV2/Types.hs | 1 + 2 files changed, 27 insertions(+), 4 deletions(-) diff --git a/unison-cli/src/Unison/Share/SyncV2.hs b/unison-cli/src/Unison/Share/SyncV2.hs index 4eda9ac8d9..de7bbbef01 100644 --- a/unison-cli/src/Unison/Share/SyncV2.hs +++ b/unison-cli/src/Unison/Share/SyncV2.hs @@ -63,7 +63,7 @@ import Unison.Sync.Types qualified as Share import Unison.Sync.Types qualified as Sync import Unison.SyncV2.API (Routes (downloadEntitiesStream)) import Unison.SyncV2.API qualified as SyncV2 -import Unison.SyncV2.Types (CBORBytes, CBORStream) +import Unison.SyncV2.Types (CBORBytes, CBORStream, DependencyType (..)) import Unison.SyncV2.Types qualified as SyncV2 import Unison.Util.Servant.CBOR qualified as CBOR import Unison.Util.Timing qualified as Timing @@ -566,11 +566,33 @@ negotiateKnownCausals unisonShareUrl branchRef hashJwt = do unisonShareUrl SyncV2.CausalDependenciesRequest {branchRef, rootCausal = hashJwt} \stream -> do - Set.fromList <$> C.runConduit (stream C..| C.map unpack C..| C.filterM (haveCausalHash codebase) C..| C.sinkList) + Set.fromList <$> C.runConduit (stream C..| C.map unpack C..| findKnownDeps codebase C..| C.sinkList) where - unpack :: SyncV2.CausalDependenciesChunk -> Hash32 + -- Go through the dependencies of the remote root from top-down, yielding all causal hashes that we already + -- have until we find one in the causal spine we already have, then yield that one and stop since we'll implicitly + -- have all of its dependencies. + findKnownDeps :: Codebase.Codebase IO v a -> Stream (Hash32, DependencyType) Hash32 + findKnownDeps codebase = do + C.await >>= \case + Just (hash, LibDependency) -> do + -- We yield all lib dependencies we have, it's possible we don't have any of the causal spine in common, but _do_ have + -- some of the libraries we can still save a lot of work. + whenM (lift $ haveCausalHash codebase hash) (C.yield hash) + -- We continue regardless. + findKnownDeps codebase + Just (hash, CausalSpineDependency) -> do + lift (haveCausalHash codebase hash) >>= \case + True -> do + -- If we find a causal hash we have in the spine, we don't need to look further, + -- we can pass it on, then hang up the stream. + C.yield hash + False -> do + -- Otherwise we keep looking, maybe we'll have one further in. + findKnownDeps codebase + Nothing -> pure () + unpack :: SyncV2.CausalDependenciesChunk -> (Hash32, DependencyType) unpack = \case - SyncV2.CausalHashDepC {causalHash} -> causalHash + SyncV2.CausalHashDepC {causalHash, dependencyType} -> (causalHash, dependencyType) haveCausalHash :: Codebase.Codebase IO v a -> Hash32 -> StreamM Bool haveCausalHash codebase causalHash = do liftIO $ Codebase.runTransaction codebase do diff --git a/unison-share-api/src/Unison/SyncV2/Types.hs b/unison-share-api/src/Unison/SyncV2/Types.hs index 52f6c543b8..0a716a5c37 100644 --- a/unison-share-api/src/Unison/SyncV2/Types.hs +++ b/unison-share-api/src/Unison/SyncV2/Types.hs @@ -10,6 +10,7 @@ module Unison.SyncV2.Types DownloadEntitiesError (..), CausalDependenciesRequest (..), CausalDependenciesChunk (..), + DependencyType (..), CBORBytes (..), CBORStream (..), EntityKind (..), From 51cf2b2b4c22acc5ba051282b84f4ecdbc6ed80b Mon Sep 17 00:00:00 2001 From: Chris Penner Date: Mon, 3 Feb 2025 16:47:49 -0800 Subject: [PATCH 5/8] Clear temp entity tables before starting a syncv2 --- unison-cli/src/Unison/Share/SyncV2.hs | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/unison-cli/src/Unison/Share/SyncV2.hs b/unison-cli/src/Unison/Share/SyncV2.hs index de7bbbef01..7ec0181ae4 100644 --- a/unison-cli/src/Unison/Share/SyncV2.hs +++ b/unison-cli/src/Unison/Share/SyncV2.hs @@ -117,6 +117,9 @@ syncFromFile :: Cli (Either (SyncError SyncV2.PullError) CausalHash) syncFromFile shouldValidate syncFilePath = do Cli.Env {codebase} <- ask + -- Every insert into SQLite checks the temp entity tables, but syncv2 doesn't actually use them, so it's faster + -- if we clear them out before starting a sync. + Cli.runTransaction Q.clearTempEntityTables runExceptT do mapExceptT liftIO $ Timing.time "File Sync" $ do header <- mapExceptT C.runResourceT $ do @@ -136,6 +139,9 @@ syncFromCodebase :: CausalHash -> IO (Either (SyncError SyncV2.PullError) ()) syncFromCodebase shouldValidate srcConn destCodebase causalHash = do + -- Every insert into SQLite checks the temp entity tables, but syncv2 doesn't actually use them, so it's faster + -- if we clear them out before starting a sync. + Sqlite.runTransaction srcConn Q.clearTempEntityTables liftIO . C.runResourceT . runExceptT $ withCodebaseEntityStream srcConn causalHash Nothing \_total entityStream -> do (header, rest) <- initializeStream entityStream streamIntoCodebase shouldValidate destCodebase header rest @@ -154,6 +160,9 @@ syncFromCodeserver :: Cli (Either (SyncError SyncV2.PullError) ()) syncFromCodeserver shouldValidate unisonShareUrl branchRef hashJwt _downloadedCallback = do Cli.Env {authHTTPClient, codebase} <- ask + -- Every insert into SQLite checks the temp entity tables, but syncv2 doesn't actually use them, so it's faster + -- if we clear them out before starting a sync. + Cli.runTransaction Q.clearTempEntityTables runExceptT do knownHashes <- ExceptT $ negotiateKnownCausals unisonShareUrl branchRef hashJwt let hash = Share.hashJWTHash hashJwt From 40af0b1aacf75fd45b110cf2dd24abf156dc224d Mon Sep 17 00:00:00 2001 From: Chris Penner Date: Tue, 4 Feb 2025 20:56:12 -0800 Subject: [PATCH 6/8] Progress tick on negotiation --- unison-cli/src/Unison/Share/SyncV2.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/unison-cli/src/Unison/Share/SyncV2.hs b/unison-cli/src/Unison/Share/SyncV2.hs index 7ec0181ae4..d3b215c4a2 100644 --- a/unison-cli/src/Unison/Share/SyncV2.hs +++ b/unison-cli/src/Unison/Share/SyncV2.hs @@ -569,6 +569,7 @@ negotiateKnownCausals :: Cli (Either (SyncError SyncV2.PullError) (Set Hash32)) negotiateKnownCausals unisonShareUrl branchRef hashJwt = do Cli.Env {authHTTPClient, codebase} <- ask + liftIO $ Text.hPutStrLn IO.stderr $ " 🔎 Identifying missing entities..." Timing.time "Causal Negotiation" $ do liftIO . C.runResourceT . runExceptT $ httpStreamCausalDependencies authHTTPClient From 9516179a79dfa73d30d8a91220d43a098f4e70f5 Mon Sep 17 00:00:00 2001 From: Chris Penner Date: Wed, 5 Feb 2025 10:15:38 -0800 Subject: [PATCH 7/8] Set Sync version via env var --- docs/configuration.md | 13 ++++++++++-- unison-cli/src/Unison/Cli/DownloadUtils.hs | 17 ++++++++++++--- .../src/Unison/Codebase/Editor/HandleInput.hs | 2 +- .../Codebase/Editor/HandleInput/InstallLib.hs | 2 +- .../Editor/HandleInput/ProjectClone.hs | 4 ++-- .../Editor/HandleInput/ProjectCreate.hs | 4 ++-- .../Codebase/Editor/HandleInput/Pull.hs | 5 ++--- .../Codebase/Editor/HandleInput/SyncV2.hs | 4 ++-- .../src/Unison/Codebase/Editor/Input.hs | 6 +----- .../src/Unison/CommandLine/InputPatterns.hs | 21 ++++++------------- unison-cli/src/Unison/Share/SyncV2.hs | 2 +- 11 files changed, 43 insertions(+), 37 deletions(-) diff --git a/docs/configuration.md b/docs/configuration.md index 549f274a2a..87d38dca3a 100644 --- a/docs/configuration.md +++ b/docs/configuration.md @@ -10,6 +10,7 @@ * [`UNISON_SHARE_ACCESS_TOKEN`](#unison_share_access_token) * [`UNISON_READONLY`](#unison_readonly) * [`UNISON_ENTITY_VALIDATION`](#unison_entity_validation) + * [`UNISON_SYNC_VERSION`](#unison_sync_version) * [Local Codebase Server](#local-codebase-server) * [Codebase Configuration](#codebase-configuration) @@ -17,7 +18,7 @@ ### `UNISON_DEBUG` -Enable debugging output for various portions of the application. +Enable debugging output for various portions of the application. See `lib/unison-prelude/src/Unison/Debug.hs` for the full list of supported flags. E.g. @@ -62,7 +63,7 @@ Note for Windows users: Due to an outstanding issue with GHC's IO manager on Win Enabling the LSP on windows can cause UCM to hang on exit and may require the process to be killed by the operating system or via Ctrl-C. Note that this doesn't pose any risk of codebase corruption or cause any known issues, it's simply an annoyance. -If you accept this annoyance, you can enable the LSP server on Windows by exporting the `UNISON_LSP_ENABLED=true` environment variable. +If you accept this annoyance, you can enable the LSP server on Windows by exporting the `UNISON_LSP_ENABLED=true` environment variable. You can set this persistently in powershell using: @@ -117,6 +118,14 @@ Defaults to enabled. $ UNISON_ENTITY_VALIDATION="false" ucm ``` +### `UNISON_SYNC_VERSION` + +Allows enabling the experimental Sync Version 2 protocol when downloading code from Share. + +```sh +$ UNISON_ENTITY_VALIDATION="2" ucm +``` + ### `UNISON_PULL_WORKERS` Allows setting the number of workers to use when pulling from a codebase server. diff --git a/unison-cli/src/Unison/Cli/DownloadUtils.hs b/unison-cli/src/Unison/Cli/DownloadUtils.hs index 68c21dc6a2..936b2b3fba 100644 --- a/unison-cli/src/Unison/Cli/DownloadUtils.hs +++ b/unison-cli/src/Unison/Cli/DownloadUtils.hs @@ -12,13 +12,13 @@ import Control.Concurrent.STM (atomically) import Control.Concurrent.STM.TVar (modifyTVar', newTVarIO, readTVar, readTVarIO) import Data.List.NonEmpty (pattern (:|)) import System.Console.Regions qualified as Console.Regions +import System.IO.Unsafe (unsafePerformIO) import U.Codebase.HashTags (CausalHash) import U.Codebase.Sqlite.Queries qualified as Queries import Unison.Cli.Monad (Cli) import Unison.Cli.Monad qualified as Cli import Unison.Cli.Share.Projects qualified as Share import Unison.Codebase.Editor.HandleInput.AuthLogin (ensureAuthenticatedWithCodeserver) -import Unison.Codebase.Editor.Input (SyncVersion (..)) import Unison.Codebase.Editor.Output qualified as Output import Unison.Codebase.Editor.RemoteRepo (ReadShareLooseCode, shareUserHandleToText) import Unison.Codebase.Editor.RemoteRepo qualified as RemoteRepo @@ -35,15 +35,26 @@ import Unison.Share.Types (codeserverBaseURL) import Unison.Sync.Common qualified as Sync.Common import Unison.Sync.Types qualified as Share import Unison.SyncV2.Types qualified as SyncV2 +import UnliftIO.Environment qualified as UnliftIO + +data SyncVersion = SyncV1 | SyncV2 + deriving (Eq, Show) + +-- | The version of the sync protocol to use. +syncVersion :: SyncVersion +syncVersion = unsafePerformIO do + UnliftIO.lookupEnv "UNISON_SYNC_VERSION" + <&> \case + Just "2" -> SyncV2 + _ -> SyncV1 -- | Download a project/branch from Share. downloadProjectBranchFromShare :: (HasCallStack) => - SyncVersion -> Share.IncludeSquashedHead -> Share.RemoteProjectBranch -> Cli (Either Output.ShareError CausalHash) -downloadProjectBranchFromShare syncVersion useSquashed branch = +downloadProjectBranchFromShare useSquashed branch = Cli.labelE \done -> do let remoteProjectBranchName = branch.branchName causalHashJwt <- diff --git a/unison-cli/src/Unison/Codebase/Editor/HandleInput.hs b/unison-cli/src/Unison/Codebase/Editor/HandleInput.hs index 6675a49843..3924afa1aa 100644 --- a/unison-cli/src/Unison/Codebase/Editor/HandleInput.hs +++ b/unison-cli/src/Unison/Codebase/Editor/HandleInput.hs @@ -667,7 +667,7 @@ loop e = do _ <- Cli.updateAtM description pp \destb -> liftIO (Branch.merge'' (Codebase.lca codebase) Branch.RegularMerge srcb destb) Cli.respond Success - PullI syncVersion sourceTarget pullMode -> handlePull syncVersion sourceTarget pullMode + PullI sourceTarget pullMode -> handlePull sourceTarget pullMode PushRemoteBranchI pushRemoteBranchInput -> handlePushRemoteBranch pushRemoteBranchInput SyncToFileI syncFileDest projectBranchName -> SyncV2.handleSyncToFile syncFileDest projectBranchName SyncFromFileI syncFileSrc projectBranchName -> do diff --git a/unison-cli/src/Unison/Codebase/Editor/HandleInput/InstallLib.hs b/unison-cli/src/Unison/Codebase/Editor/HandleInput/InstallLib.hs index 299f30ba47..52e70188c8 100644 --- a/unison-cli/src/Unison/Codebase/Editor/HandleInput/InstallLib.hs +++ b/unison-cli/src/Unison/Codebase/Editor/HandleInput/InstallLib.hs @@ -60,7 +60,7 @@ handleInstallLib remind (ProjectAndBranch libdepProjectName unresolvedLibdepBran Cli.Env {codebase} <- ask causalHash <- - downloadProjectBranchFromShare SyncV1 Share.IncludeSquashedHead libdepProjectBranch + downloadProjectBranchFromShare Share.IncludeSquashedHead libdepProjectBranch & onLeftM (Cli.returnEarly . Output.ShareError) remoteBranchObject <- liftIO (Codebase.expectBranchForHash codebase causalHash) diff --git a/unison-cli/src/Unison/Codebase/Editor/HandleInput/ProjectClone.hs b/unison-cli/src/Unison/Codebase/Editor/HandleInput/ProjectClone.hs index 670a730b5e..8a872d18b8 100644 --- a/unison-cli/src/Unison/Codebase/Editor/HandleInput/ProjectClone.hs +++ b/unison-cli/src/Unison/Codebase/Editor/HandleInput/ProjectClone.hs @@ -13,7 +13,7 @@ import U.Codebase.Sqlite.Project qualified as Sqlite (Project (..)) import U.Codebase.Sqlite.ProjectBranch qualified as Sqlite import U.Codebase.Sqlite.Queries qualified as Q import U.Codebase.Sqlite.Queries qualified as Queries -import Unison.Cli.DownloadUtils (SyncVersion (..), downloadProjectBranchFromShare) +import Unison.Cli.DownloadUtils (downloadProjectBranchFromShare) import Unison.Cli.Monad (Cli) import Unison.Cli.Monad qualified as Cli import Unison.Cli.MonadUtils qualified as Cli (getCurrentProjectAndBranch) @@ -225,7 +225,7 @@ cloneInto localProjectBranch remoteProjectBranch = do let remoteProjectBranchNames = ProjectAndBranch remoteProjectName remoteBranchName branchHead <- - downloadProjectBranchFromShare SyncV1 Share.NoSquashedHead remoteProjectBranch + downloadProjectBranchFromShare Share.NoSquashedHead remoteProjectBranch & onLeftM (Cli.returnEarly . Output.ShareError) localProjectAndBranch <- diff --git a/unison-cli/src/Unison/Codebase/Editor/HandleInput/ProjectCreate.hs b/unison-cli/src/Unison/Codebase/Editor/HandleInput/ProjectCreate.hs index 0096a91d8d..e9f6e99e95 100644 --- a/unison-cli/src/Unison/Codebase/Editor/HandleInput/ProjectCreate.hs +++ b/unison-cli/src/Unison/Codebase/Editor/HandleInput/ProjectCreate.hs @@ -13,7 +13,7 @@ import U.Codebase.Sqlite.Project (Project (..)) import U.Codebase.Sqlite.ProjectBranch (ProjectBranch (..)) import U.Codebase.Sqlite.Queries (expectCausalHashIdByCausalHash) import U.Codebase.Sqlite.Queries qualified as Queries -import Unison.Cli.DownloadUtils (SyncVersion (..), downloadProjectBranchFromShare) +import Unison.Cli.DownloadUtils (downloadProjectBranchFromShare) import Unison.Cli.Monad (Cli) import Unison.Cli.Monad qualified as Cli import Unison.Cli.Share.Projects qualified as Share @@ -108,7 +108,7 @@ projectCreate tryDownloadingBase maybeProjectName = do Share.GetProjectBranchResponseBranchNotFound -> done Nothing Share.GetProjectBranchResponseProjectNotFound -> done Nothing Share.GetProjectBranchResponseSuccess branch -> pure branch - downloadProjectBranchFromShare SyncV1 Share.NoSquashedHead baseLatestReleaseBranch + downloadProjectBranchFromShare Share.NoSquashedHead baseLatestReleaseBranch & onLeftM (Cli.returnEarly . Output.ShareError) Cli.Env {codebase} <- ask baseLatestReleaseBranchObject <- diff --git a/unison-cli/src/Unison/Codebase/Editor/HandleInput/Pull.hs b/unison-cli/src/Unison/Codebase/Editor/HandleInput/Pull.hs index e51ba1046a..3ff7012220 100644 --- a/unison-cli/src/Unison/Codebase/Editor/HandleInput/Pull.hs +++ b/unison-cli/src/Unison/Codebase/Editor/HandleInput/Pull.hs @@ -46,8 +46,8 @@ import Unison.Prelude import Unison.Project (ProjectAndBranch (..), ProjectBranchNameOrLatestRelease (..), ProjectName) import Witch (unsafeFrom) -handlePull :: SyncVersion -> PullSourceTarget -> PullMode -> Cli () -handlePull syncVersion unresolvedSourceAndTarget pullMode = do +handlePull :: PullSourceTarget -> PullMode -> Cli () +handlePull unresolvedSourceAndTarget pullMode = do let includeSquashed = case pullMode of Input.PullWithHistory -> Share.NoSquashedHead Input.PullWithoutHistory -> Share.IncludeSquashedHead @@ -59,7 +59,6 @@ handlePull syncVersion unresolvedSourceAndTarget pullMode = do ReadShare'LooseCode repo -> downloadLooseCodeFromShare repo & onLeftM (Cli.returnEarly . Output.ShareError) ReadShare'ProjectBranch remoteBranch -> downloadProjectBranchFromShare - syncVersion ( case pullMode of Input.PullWithHistory -> Share.NoSquashedHead Input.PullWithoutHistory -> Share.IncludeSquashedHead diff --git a/unison-cli/src/Unison/Codebase/Editor/HandleInput/SyncV2.hs b/unison-cli/src/Unison/Codebase/Editor/HandleInput/SyncV2.hs index 015e5b7630..39af010bfe 100644 --- a/unison-cli/src/Unison/Codebase/Editor/HandleInput/SyncV2.hs +++ b/unison-cli/src/Unison/Codebase/Editor/HandleInput/SyncV2.hs @@ -10,7 +10,7 @@ import Control.Lens import Control.Monad.Reader (MonadReader (..)) import U.Codebase.HashTags (CausalHash) import U.Codebase.Sqlite.Queries qualified as Q -import Unison.Cli.DownloadUtils (SyncVersion (..), downloadProjectBranchFromShare) +import Unison.Cli.DownloadUtils (downloadProjectBranchFromShare) import Unison.Cli.Monad (Cli) import Unison.Cli.Monad qualified as Cli import Unison.Cli.MonadUtils qualified as Cli @@ -75,4 +75,4 @@ handleSyncFromCodebase description srcCodebasePath srcBranch destBranch = do Cli.respond (Output.SyncPullError syncErr) handleSyncFromCodeserver :: Projects.IncludeSquashedHead -> Projects.RemoteProjectBranch -> Cli (Either Output.ShareError CausalHash) -handleSyncFromCodeserver = downloadProjectBranchFromShare SyncV2 +handleSyncFromCodeserver = downloadProjectBranchFromShare diff --git a/unison-cli/src/Unison/Codebase/Editor/Input.hs b/unison-cli/src/Unison/Codebase/Editor/Input.hs index b386cd98b2..75de97cd1a 100644 --- a/unison-cli/src/Unison/Codebase/Editor/Input.hs +++ b/unison-cli/src/Unison/Codebase/Editor/Input.hs @@ -31,7 +31,6 @@ module Unison.Codebase.Editor.Input -- * Type aliases ErrorMessageOrName, RawQuery, - SyncVersion (..), ) where @@ -60,9 +59,6 @@ data Event = UnisonFileChanged SourceName Source deriving stock (Show) -data SyncVersion = SyncV1 | SyncV2 - deriving (Eq, Show) - type Source = Text -- "id x = x\nconst a b = a" type SourceName = Text -- "foo.u" or "buffer 7" @@ -138,7 +134,7 @@ data Input MergeLocalBranchI BranchRelativePath (Maybe BranchRelativePath) Branch.MergeMode | PreviewMergeLocalBranchI BranchRelativePath (Maybe BranchRelativePath) | DiffNamespaceI BranchId2 BranchId2 -- old new - | PullI !SyncVersion !PullSourceTarget !PullMode + | PullI !PullSourceTarget !PullMode | PushRemoteBranchI PushRemoteBranchInput | SyncToFileI FilePath (ProjectAndBranch (Maybe ProjectName) (Maybe ProjectBranchName)) | SyncFromFileI FilePath UnresolvedProjectBranch diff --git a/unison-cli/src/Unison/CommandLine/InputPatterns.hs b/unison-cli/src/Unison/CommandLine/InputPatterns.hs index c17759e418..b003e374a2 100644 --- a/unison-cli/src/Unison/CommandLine/InputPatterns.hs +++ b/unison-cli/src/Unison/CommandLine/InputPatterns.hs @@ -92,7 +92,6 @@ module Unison.CommandLine.InputPatterns projectSwitch, projectsInputPattern, pull, - pullV2, pullWithoutHistory, push, pushCreate, @@ -1788,13 +1787,7 @@ reset = pull :: InputPattern pull = - pullImpl "pull" [] Input.PullWithHistory "" Input.SyncV1 - -pullV2 :: InputPattern -pullV2 = - (pullImpl "pull.v2" [] Input.PullWithHistory "" Input.SyncV2) - {I.visibility = I.Hidden - } + pullImpl "pull" [] Input.PullWithHistory "" pullWithoutHistory :: InputPattern pullWithoutHistory = @@ -1803,10 +1796,9 @@ pullWithoutHistory = [] Input.PullWithoutHistory "without including the remote's history. This usually results in smaller codebase sizes." - Input.SyncV1 -pullImpl :: String -> [String] -> Input.PullMode -> P.Pretty CT.ColorText -> Input.SyncVersion -> InputPattern -pullImpl name aliases pullMode addendum syncVersion = do +pullImpl :: String -> [String] -> Input.PullMode -> P.Pretty CT.ColorText -> InputPattern +pullImpl name aliases pullMode addendum = do self where self = @@ -1850,10 +1842,10 @@ pullImpl name aliases pullMode addendum syncVersion = do explainRemote Pull ], parse = \case - [] -> pure $ Input.PullI syncVersion Input.PullSourceTarget0 pullMode + [] -> pure $ Input.PullI Input.PullSourceTarget0 pullMode [sourceArg] -> do source <- handlePullSourceArg sourceArg - pure (Input.PullI syncVersion (Input.PullSourceTarget1 source) pullMode) + pure (Input.PullI (Input.PullSourceTarget1 source) pullMode) [sourceArg, targetArg] -> -- You used to be able to pull into a path, so this arg parser is a little complicated, because -- we want to provide helpful suggestions if you are doing a deprecated or invalid thing. @@ -1861,7 +1853,7 @@ pullImpl name aliases pullMode addendum syncVersion = do handleMaybeProjectBranchArg targetArg, handlePath'Arg targetArg ) of - (Right source, Right target, _) -> Right (Input.PullI syncVersion (Input.PullSourceTarget2 source target) pullMode) + (Right source, Right target, _) -> Right (Input.PullI (Input.PullSourceTarget2 source target) pullMode) (Left err, _, _) -> Left err -- Parsing as a path didn't work either; just show the branch parse error (Right _, Left err, Left _) -> Left err @@ -3821,7 +3813,6 @@ validInputs = projectSwitch, projectsInputPattern, pull, - pullV2, pullWithoutHistory, push, pushCreate, diff --git a/unison-cli/src/Unison/Share/SyncV2.hs b/unison-cli/src/Unison/Share/SyncV2.hs index d3b215c4a2..14870f208d 100644 --- a/unison-cli/src/Unison/Share/SyncV2.hs +++ b/unison-cli/src/Unison/Share/SyncV2.hs @@ -569,7 +569,7 @@ negotiateKnownCausals :: Cli (Either (SyncError SyncV2.PullError) (Set Hash32)) negotiateKnownCausals unisonShareUrl branchRef hashJwt = do Cli.Env {authHTTPClient, codebase} <- ask - liftIO $ Text.hPutStrLn IO.stderr $ " 🔎 Identifying missing entities..." + liftIO $ Text.hPutStrLn IO.stderr $ " 🔎 Identifying missing entities..." Timing.time "Causal Negotiation" $ do liftIO . C.runResourceT . runExceptT $ httpStreamCausalDependencies authHTTPClient From c8d360d184f275054ea7e10046470810e0a8c47d Mon Sep 17 00:00:00 2001 From: Chris Penner Date: Wed, 5 Feb 2025 11:13:16 -0800 Subject: [PATCH 8/8] Update transcript output --- .../project-outputs/docs/configuration.output.md | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/unison-src/transcripts/project-outputs/docs/configuration.output.md b/unison-src/transcripts/project-outputs/docs/configuration.output.md index 0bf4d06de5..bcae1f8b5a 100644 --- a/unison-src/transcripts/project-outputs/docs/configuration.output.md +++ b/unison-src/transcripts/project-outputs/docs/configuration.output.md @@ -9,6 +9,7 @@ - [`UNISON_SHARE_ACCESS_TOKEN`](#unison_share_access_token) - [`UNISON_READONLY`](#unison_readonly) - [`UNISON_ENTITY_VALIDATION`](#unison_entity_validation) + - [`UNISON_SYNC_VERSION`](#unison_sync_version) - [Local Codebase Server](#local-codebase-server) - [Codebase Configuration](#codebase-configuration) @@ -116,6 +117,14 @@ Defaults to enabled. $ UNISON_ENTITY_VALIDATION="false" ucm ``` +### `UNISON_SYNC_VERSION` + +Allows enabling the experimental Sync Version 2 protocol when downloading code from Share. + +``` sh +$ UNISON_ENTITY_VALIDATION="2" ucm +``` + ### `UNISON_PULL_WORKERS` Allows setting the number of workers to use when pulling from a codebase server.