This commit is contained in:
voidlizard 2025-01-22 06:17:59 +03:00
parent d9cd91398a
commit f2027bb19e
12 changed files with 218 additions and 166 deletions

View File

@ -64,7 +64,8 @@ symlinks: $(BIN_DIR)
> path=`find dist-newstyle -type f -name $$bin -path "*$(GHC_VERSION)*" | head -n 1`; \ > path=`find dist-newstyle -type f -name $$bin -path "*$(GHC_VERSION)*" | head -n 1`; \
> if [ -n "$$path" ]; then \ > if [ -n "$$path" ]; then \
> echo "Creating symlink for $$bin"; \ > echo "Creating symlink for $$bin"; \
> ln -sf $$PWD/$$path $(BIN_DIR)/$$bin; \ > ln -sfn $$PWD/$$path $(BIN_DIR)/$$bin; \
#> cp $$PWD/$$path $(BIN_DIR)/$$bin; \
> else \ > else \
> echo "Binary $$bin for GHC $(GHC_VERSION) not found"; \ > echo "Binary $$bin for GHC $(GHC_VERSION) not found"; \
> fi; \ > fi; \

View File

@ -18,6 +18,24 @@
"type": "github" "type": "github"
} }
}, },
"flake-utils_2": {
"inputs": {
"systems": "systems_2"
},
"locked": {
"lastModified": 1731533236,
"narHash": "sha256-l0KFg5HjrsfsO/JpG+r7fRrqm12kzFHyUHqHCVpMMbI=",
"owner": "numtide",
"repo": "flake-utils",
"rev": "11707dc2f618dd54ca8739b309ec4fc024de578b",
"type": "github"
},
"original": {
"owner": "numtide",
"repo": "flake-utils",
"type": "github"
}
},
"haskell-flake-utils": { "haskell-flake-utils": {
"inputs": { "inputs": {
"flake-utils": [ "flake-utils": [
@ -62,6 +80,27 @@
"type": "github" "type": "github"
} }
}, },
"nixbwrap": {
"inputs": {
"flake-utils": "flake-utils_2",
"nixpkgs": [
"nixpkgs"
]
},
"locked": {
"lastModified": 1667333413,
"narHash": "sha256-QGR6Src6UNXac3fgoe9PW40bAOYy0f05DGcRD2ae2S4=",
"ref": "refs/heads/master",
"rev": "a24e9553ee84d01aa2f9b35f30c75728864dfa52",
"revCount": 28,
"type": "git",
"url": "https://git.sr.ht/~fgaz/nix-bubblewrap"
},
"original": {
"type": "git",
"url": "https://git.sr.ht/~fgaz/nix-bubblewrap"
}
},
"nixpkgs": { "nixpkgs": {
"locked": { "locked": {
"lastModified": 1727089097, "lastModified": 1727089097,
@ -83,6 +122,7 @@
"flake-utils": "flake-utils", "flake-utils": "flake-utils",
"haskell-flake-utils": "haskell-flake-utils", "haskell-flake-utils": "haskell-flake-utils",
"hspup": "hspup", "hspup": "hspup",
"nixbwrap": "nixbwrap",
"nixpkgs": "nixpkgs" "nixpkgs": "nixpkgs"
} }
}, },
@ -100,6 +140,21 @@
"repo": "default", "repo": "default",
"type": "github" "type": "github"
} }
},
"systems_2": {
"locked": {
"lastModified": 1681028828,
"narHash": "sha256-Vy1rq5AaRuLzOxct8nz4T6wlgyUR7zLU309k9mBC768=",
"owner": "nix-systems",
"repo": "default",
"rev": "da67096a3b9bf56a91d16901293e51ba5b49a27e",
"type": "github"
},
"original": {
"owner": "nix-systems",
"repo": "default",
"type": "github"
}
} }
}, },
"root": "root", "root": "root",

View File

@ -14,6 +14,9 @@ inputs = {
hspup.inputs.nixpkgs.follows = "nixpkgs"; hspup.inputs.nixpkgs.follows = "nixpkgs";
hspup.inputs.haskell-flake-utils.follows = "haskell-flake-utils"; hspup.inputs.haskell-flake-utils.follows = "haskell-flake-utils";
nixbwrap.url = "git+https://git.sr.ht/~fgaz/nix-bubblewrap";
nixbwrap.inputs.nixpkgs.follows = "nixpkgs";
}; };
outputs = { self, nixpkgs, flake-utils, ... }@inputs: outputs = { self, nixpkgs, flake-utils, ... }@inputs:
@ -159,6 +162,8 @@ outputs = { self, nixpkgs, flake-utils, ... }@inputs:
pkgs.icu72 pkgs.icu72
pkgs.openssl pkgs.openssl
weeder weeder
pkgs.iptables
pkgs.bridge-utils
] ]
++ ++
[ pkgs.pkg-config [ pkgs.pkg-config
@ -166,6 +171,7 @@ outputs = { self, nixpkgs, flake-utils, ... }@inputs:
pkgs.file pkgs.file
pkgs.zlib pkgs.zlib
inputs.hspup.packages.${pkgs.system}.default inputs.hspup.packages.${pkgs.system}.default
inputs.nixbwrap.packages.${pkgs.system}.default
] ]
); );

View File

@ -114,13 +114,9 @@ localDict DeferredOps{..} = makeDict @C do
t0 <- getTimeCoarse t0 <- getTimeCoarse
flip fix 0 $ \next i -> do -- waitRepo Nothing
importGitRefLog >>= \case
Just{} -> none importGitRefLog
Nothing -> do
notice "wait for data..."
pause @'Seconds 2.0
next (succ i)
rrefs <- importedRefs rrefs <- importedRefs
@ -198,16 +194,17 @@ main = flip runContT pure do
cli <- parseCLI cli <- parseCLI
case cli of url <- case cli of
[ ListVal [_, RepoURL url ] ] -> do [ ListVal [_, RepoURL x ] ] -> do
notice $ "FUCKING REMOTE" <+> pretty (AsBase58 url) notice $ "FUCKING REMOTE" <+> pretty (AsBase58 x)
setGitRepoKey url setGitRepoKey x
pure $ Just x
_ -> none _ -> pure Nothing
recover $ connectedDo $ withStateDo do
void $ run dict conf void $ run dict conf
for_ url updateRepoKey
recover $ connectedDo do
flip fix Plain $ \next -> \case flip fix Plain $ \next -> \case
Plain -> do Plain -> do

View File

@ -82,7 +82,6 @@ main = flip runContT pure do
cli <- parseTop (unlines $ unwords <$> splitForms argz) cli <- parseTop (unlines $ unwords <$> splitForms argz)
& either (error.show) pure & either (error.show) pure
env <- nullGit3Env env <- nullGit3Env
void $ lift $ withGit3Env env do void $ lift $ withGit3Env env do

View File

@ -6,43 +6,15 @@ import HBS2.System.Dir
import HBS2.Git.Local.CLI import HBS2.Git.Local.CLI
import System.Directory import Control.Monad.Trans.Maybe
import Data.Config.Suckless.Script
import Data.Text.IO qualified as IO
{- HLINT ignore "Functor law"-} {- HLINT ignore "Functor law"-}
getConfigPath :: MonadIO m => m FilePath getConfigPath :: MonadIO m => m (Maybe FilePath)
getConfigPath = do getConfigPath = do
let name = ".hbs2-git3" let name = ".hbs2-git3"
runMaybeT do
gitDir gitDir
>>= orThrowUser ".git not found" >>= toMPlus <&> (</> name) . takeDirectory
<&> (</> name) . takeDirectory
getConfigRootFile :: MonadIO m => m FilePath
getConfigRootFile = do
let name = ".hbs2-git3"
gitDir
>>= orThrowUser ".git not found"
<&> (</> name) . takeDirectory
<&> (</> "config")
readLocalConf :: MonadIO m => m [Syntax C]
readLocalConf = do
conf <- getConfigPath <&> (</> "config")
touch conf
liftIO (IO.readFile conf)
<&> parseTop
>>= either (const $ pure mempty) pure

View File

@ -86,7 +86,7 @@ exportEntries prefix = do
export (Just h) refs export (Just h) refs
export :: forall m . HBS2GitPerks m => Maybe GitHash -> [(GitRef, GitHash)] -> Git3 m () export :: forall m . HBS2GitPerks m => Maybe GitHash -> [(GitRef, GitHash)] -> Git3 m ()
export mbh refs = do export mbh refs = withStateDo do
tn <- getNumCapabilities tn <- getNumCapabilities
updateReflogIndex updateReflogIndex
@ -281,9 +281,11 @@ export mbh refs = do
where where
writeLogEntry e = do writeLogEntry e = do
path <- getConfigPath <&> (</> "log") path' <- getConfigPath
for_ path' $ \path -> do
let logPath = path </> "log"
touch path touch path
liftIO (IO.appendFile path (show $ e <> line)) liftIO (IO.appendFile logPath (show $ e <> line))
writeRefSectionSome :: forall m1 . MonadIO m1 => TBQueue (Maybe LBS.ByteString) -> [(GitRef, GitHash)] -> m1 () writeRefSectionSome :: forall m1 . MonadIO m1 => TBQueue (Maybe LBS.ByteString) -> [(GitRef, GitHash)] -> m1 ()
writeRefSectionSome sourceQ refsAndCommits = do writeRefSectionSome sourceQ refsAndCommits = do

View File

@ -106,15 +106,15 @@ writeAsGitPack dir href = do
importGitRefLog :: forall m . ( HBS2GitPerks m importGitRefLog :: forall m . ( HBS2GitPerks m
, HasStorage m -- , HasStorage m
, HasClientAPI PeerAPI UNIX m -- , HasClientAPI PeerAPI UNIX m
, HasClientAPI RefLogAPI UNIX m -- , HasClientAPI RefLogAPI UNIX m
, HasGitRemoteKey m -- , HasGitRemoteKey m
, MonadReader Git3Env m -- , MonadReader Git3Env m
) )
=> m (Maybe HashRef) => Git3 m (Maybe HashRef)
importGitRefLog = do importGitRefLog = withStateDo do
updateReflogIndex updateReflogIndex

View File

@ -55,7 +55,7 @@ theDict = do
where where
myEntries = hidePrefix "test:" do myEntries = do
entry $ bindMatch "--help" $ nil_ $ \case entry $ bindMatch "--help" $ nil_ $ \case
HelpEntryBound what -> do HelpEntryBound what -> do
helpEntry what helpEntry what
@ -432,34 +432,6 @@ compression ; prints compression level
entry $ bindMatch "reflog:refs:raw" $ nil_ $ \syn -> lift $ connectedDo do entry $ bindMatch "reflog:refs:raw" $ nil_ $ \syn -> lift $ connectedDo do
refsFiles >>= readRefsRaw >>= liftIO . mapM_ (print . pretty) refsFiles >>= readRefsRaw >>= liftIO . mapM_ (print . pretty)
-- entry $ bindMatch "reflog:refs:trimmed" $ nil_ $ \syn -> lift $ connectedDo do
-- txi <- txImported
-- raw <- readRefsRaw =<< refsFiles
-- ni_ <- newTQueueIO
-- imp_ <- newTVarIO ( mempty :: HashMap Text (Integer, GitHash, HashRef) )
-- for_ raw $ \case
-- ListVal [ SymbolVal "R", HashLike seg, LitIntVal r, GitHashLike v, TextLike n ] -> do
-- atomically do
-- if not (HS.member seg txi) then
-- writeTQueue ni_ (n, (r, v, seg))
-- else do
-- let x = (r, v, seg)
-- let fn = HM.insertWith (\a b -> if view _1 a > view _1 b then a else b) n x
-- modifyTVar imp_ fn
-- _ -> none
-- result <- atomically do
-- a <- STM.flushTQueue ni_
-- b <- readTVar imp_ <&> HM.toList
-- pure (a <> b)
-- for_ result $ \(n, (r, h, v)) -> do
-- liftIO $ print $ "R" <+> pretty h <+> pretty r <+> pretty v <+> pretty n
entry $ bindMatch "reflog:wait" $ nil_ $ \syn -> lift $ connectedDo do entry $ bindMatch "reflog:wait" $ nil_ $ \syn -> lift $ connectedDo do
let (_,argz) = splitOpts [] syn let (_,argz) = splitOpts [] syn
let t = headMay [ realToFrac x | LitIntVal x <- argz ] let t = headMay [ realToFrac x | LitIntVal x <- argz ]

View File

@ -53,6 +53,8 @@ getRefLog mf = lastMay [ x
updateRepoKey :: forall m . HBS2GitPerks m => GitRepoKey -> Git3 m () updateRepoKey :: forall m . HBS2GitPerks m => GitRepoKey -> Git3 m ()
updateRepoKey key = do updateRepoKey key = do
notice $ "updateRepoKey" <+> pretty (AsBase58 key)
setGitRepoKey key setGitRepoKey key
reflog <- getRepoManifest <&> getRefLog reflog <- getRepoManifest <&> getRefLog
@ -137,6 +139,11 @@ withGit3Env env a = runReaderT (fromGit3 a) env
runGit3 :: Git3Perks m => Git3Env -> Git3 m b -> m b runGit3 :: Git3Perks m => Git3Env -> Git3 m b -> m b
runGit3 env action = withGit3Env env action runGit3 env action = withGit3Env env action
withStateDo :: MonadUnliftIO m => Git3 m a -> Git3 m a
withStateDo action = do
waitRepo Nothing
getStatePathM >>= mkdir
action
recover :: Git3 IO a -> Git3 IO a recover :: Git3 IO a -> Git3 IO a
recover m = fix \again -> do recover m = fix \again -> do
@ -170,12 +177,13 @@ recover m = fix \again -> do
let sto = AnyStorage (StorageClient storageAPI) let sto = AnyStorage (StorageClient storageAPI)
rk <- lift $ getGitRepoKey >>= orThrow GitRepoRefNotSet rk <- lift $ getGitRepoKey
notice $ yellow $ "REPOKEY" <+> pretty (AsBase58 rk) -- debug $ yellow $ "REPOKEY" <+> pretty (AsBase58 rk)
connected <- Git3Connected soname sto peer refLogAPI lwwAPI connected <- Git3Connected soname sto peer refLogAPI lwwAPI
<$> newTVarIO (Just rk) <$> newTVarIO rk
<*> newTVarIO Nothing
<*> newTVarIO Nothing <*> newTVarIO Nothing
<*> newTVarIO defSegmentSize <*> newTVarIO defSegmentSize
<*> newTVarIO defCompressionLevel <*> newTVarIO defCompressionLevel
@ -183,14 +191,10 @@ recover m = fix \again -> do
liftIO $ withGit3Env connected do liftIO $ withGit3Env connected do
-- updateRepoKey rk
updateRepoKey rk -- ref <- getGitRemoteKey >>= orThrow GitRepoManifestMalformed
-- state <- getStatePathM
ref <- getGitRemoteKey >>= orThrow GitRepoManifestMalformed -- mkdir state
state <- getStatePath (AsBase58 ref)
mkdir state
again again
e -> throwIO e e -> throwIO e
@ -212,14 +216,22 @@ waitRepo :: forall m . HBS2GitPerks m => Maybe (Timeout 'Seconds) -> Git3 m ()
waitRepo timeout = do waitRepo timeout = do
repoKey <- getGitRepoKey >>= orThrow GitRepoRefNotSet repoKey <- getGitRepoKey >>= orThrow GitRepoRefNotSet
lwwAPI <- getClientAPI @LWWRefAPI @UNIX notice $ yellow "waitRepo"
peerAPI <- getClientAPI @PeerAPI @UNIX
reflogAPI <- getClientAPI @RefLogAPI @UNIX ask >>= \case
Git3Disconnected{} -> throwIO Git3PeerNotConnected
Git3Connected{..} -> do
sto <- getStorage sto <- getStorage
env <- ask flip runContT pure $ callCC \done -> do
flip runContT pure do rlv <- readTVarIO gitRefLogVal <&> isJust
rlog <- readTVarIO gitRefLog <&> isJust
when (rlv && rlog) $ done ()
reflog_ <- newEmptyTMVarIO
let wait w what x = pause @'Seconds w >> what x let wait w what x = pause @'Seconds w >> what x
@ -234,6 +246,12 @@ waitRepo timeout = do
void (callRpcWaitMay @RpcLWWRefFetch (TimeoutSec 1) lwwAPI (LWWRefKey repoKey)) void (callRpcWaitMay @RpcLWWRefFetch (TimeoutSec 1) lwwAPI (LWWRefKey repoKey))
pause @'Seconds 10 pause @'Seconds 10
pFetchRefLog <- ContT $ withAsync do
r <- atomically $ takeTMVar reflog_
forever do
void (callRpcWaitMay @RpcRefLogFetch (TimeoutSec 1) reflogAPI r)
pause @'Seconds 10
lww <- flip fix () \next _ -> do lww <- flip fix () \next _ -> do
notice $ "wait for" <+> pretty (AsBase58 repoKey) notice $ "wait for" <+> pretty (AsBase58 repoKey)
lift (callRpcWaitMay @RpcLWWRefGet (TimeoutSec 1) lwwAPI (LWWRefKey repoKey)) lift (callRpcWaitMay @RpcLWWRefGet (TimeoutSec 1) lwwAPI (LWWRefKey repoKey))
@ -243,8 +261,6 @@ waitRepo timeout = do
notice $ "lwwref value" <+> pretty (lwwValue lww) notice $ "lwwref value" <+> pretty (lwwValue lww)
error "stop"
mf <- flip fix () $ \next _ -> do mf <- flip fix () $ \next _ -> do
notice $ "wait for manifest" notice $ "wait for manifest"
lift (try @_ @WalkMerkleError getRepoManifest) >>= \case lift (try @_ @WalkMerkleError getRepoManifest) >>= \case
@ -253,7 +269,11 @@ waitRepo timeout = do
reflog <- getRefLog mf & orThrow GitRepoManifestMalformed reflog <- getRefLog mf & orThrow GitRepoManifestMalformed
lift $ setGitRepoKey reflog
atomically $ writeTMVar reflog_ reflog
lift (callRpcWaitMay @RpcPollAdd (TimeoutSec 1) peerAPI (reflog, "reflog", 11))
>>= orThrow RpcTimeout
rv <- flip fix () \next _ -> do rv <- flip fix () \next _ -> do
notice $ "wait for data" <+> pretty (AsBase58 reflog) notice $ "wait for data" <+> pretty (AsBase58 reflog)
@ -262,6 +282,8 @@ waitRepo timeout = do
Just (Just x) -> pure x Just (Just x) -> pure x
_ -> wait 2 next () _ -> wait 2 next ()
atomically $ writeTVar gitRefLogVal (Just rv)
okay <- newEmptyTMVarIO okay <- newEmptyTMVarIO
flip fix () $ \next _ -> do flip fix () $ \next _ -> do
@ -273,7 +295,9 @@ waitRepo timeout = do
pWait <- ContT $ withAsync $ race ( pause (fromMaybe 300 timeout) ) do pWait <- ContT $ withAsync $ race ( pause (fromMaybe 300 timeout) ) do
void $ atomically $ takeTMVar okay void $ atomically $ takeTMVar okay
waitAnyCatchCancel [pWait, pFetch] waitAnyCatchCancel [pWait, pFetch, pFetchRefLog]
lift $ updateRepoKey repoKey
liftIO $ print $ "reflog" <+> pretty (AsBase58 reflog) <+> pretty rv liftIO $ print $ "reflog" <+> pretty (AsBase58 reflog) <+> pretty rv

View File

@ -73,9 +73,8 @@ indexPath :: forall m . ( Git3Perks m
, MonadReader Git3Env m , MonadReader Git3Env m
, HasGitRemoteKey m , HasGitRemoteKey m
) => m FilePath ) => m FilePath
indexPath = do
reflog <- getGitRemoteKey >>= orThrow Git3ReflogNotSet indexPath = getStatePathM
getStatePath (AsBase58 reflog)
data IndexEntry = data IndexEntry =
IndexEntry IndexEntry
@ -129,8 +128,7 @@ mergeSortedFilesN getKey inputFiles outFile = do
compactIndex :: forall m . (Git3Perks m, HasGitRemoteKey m, MonadReader Git3Env m) => Natural -> m () compactIndex :: forall m . (Git3Perks m, HasGitRemoteKey m, MonadReader Git3Env m) => Natural -> m ()
compactIndex maxSize = do compactIndex maxSize = do
reflog <- getGitRemoteKey >>= orThrowUser "reflog not set" idxPath <- getStatePathM
idxPath <- getStatePath (AsBase58 reflog)
mkdir idxPath mkdir idxPath
files <- listObjectIndexFiles <&> L.sortOn snd files <- listObjectIndexFiles <&> L.sortOn snd

View File

@ -9,23 +9,49 @@ import HBS2.Git3.Prelude
import HBS2.Git3.Config.Local import HBS2.Git3.Config.Local
import HBS2.System.Dir import HBS2.System.Dir
import Data.Config.Suckless.Script
import Data.Kind import Data.Kind
import Data.HashSet (HashSet) import Data.HashSet (HashSet)
import Data.HashSet qualified as HS import Data.HashSet qualified as HS
import Data.Maybe
import Data.Text.IO qualified as IO
import Control.Exception qualified as E
unit :: FilePath unit :: FilePath
unit = "hbs2-git" unit = "hbs2-git"
getStatePath :: (MonadIO m, Pretty ref) => ref -> m FilePath getStatePath :: (MonadIO m, Pretty ref) => ref -> m (Maybe FilePath)
getStatePath p = do getStatePath p = runMaybeT do
d <- getConfigPath d <- getConfigPath >>= toMPlus
pure $ d </> show (pretty p) pure $ d </> show (pretty p)
getConfigRootFile :: MonadIO m => m FilePath
getConfigRootFile = do
getConfigPath
>>= orThrow StateDirNotDefined
<&> (</> "config")
readLocalConf :: MonadIO m => m [Syntax C]
readLocalConf = do
fromMaybe mempty <$> runMaybeT do
conf <- liftIO (E.try @SomeException getConfigRootFile)
>>= toMPlus
lift $ touch conf
liftIO (IO.readFile conf)
<&> parseTop
>>= either (const $ pure mempty) pure
data HBS2GitExcepion = data HBS2GitExcepion =
RefLogNotSet RefLogNotSet
| GitRepoRefNotSet | GitRepoRefNotSet
| GitRepoRefEmpty | GitRepoRefEmpty
| GitRepoManifestMalformed | GitRepoManifestMalformed
| StateDirNotDefined
| RefLogCredentialsNotMatched | RefLogCredentialsNotMatched
| RefLogNotReady | RefLogNotReady
| RpcTimeout | RpcTimeout
@ -83,6 +109,7 @@ data Git3Env =
, lwwAPI :: ServiceCaller LWWRefAPI UNIX , lwwAPI :: ServiceCaller LWWRefAPI UNIX
, gitRepoKey :: TVar (Maybe GitRepoKey) , gitRepoKey :: TVar (Maybe GitRepoKey)
, gitRefLog :: TVar (Maybe GitRemoteKey) , gitRefLog :: TVar (Maybe GitRemoteKey)
, gitRefLogVal :: TVar (Maybe HashRef)
, gitPackedSegmentSize :: TVar Int , gitPackedSegmentSize :: TVar Int
, gitCompressionLevel :: TVar Int , gitCompressionLevel :: TVar Int
, gitIndexBlockSize :: TVar Natural , gitIndexBlockSize :: TVar Natural
@ -178,9 +205,8 @@ instance (MonadUnliftIO m) => HasClientAPI LWWRefAPI UNIX (Git3 m) where
Git3Disconnected{} -> throwIO Git3PeerNotConnected Git3Disconnected{} -> throwIO Git3PeerNotConnected
Git3Connected{..} -> pure lwwAPI Git3Connected{..} -> pure lwwAPI
getStatePathM :: forall m . (HBS2GitPerks m, HasGitRemoteKey m) => m FilePath getStatePathM :: forall m . (HBS2GitPerks m, HasGitRemoteKey m) => m FilePath
getStatePathM = do getStatePathM = do
k <- getGitRemoteKey >>= orThrow RefLogNotSet k <- getGitRemoteKey >>= orThrow RefLogNotSet
getStatePath (AsBase58 k) getStatePath (AsBase58 k) >>= orThrow StateDirNotDefined