This commit is contained in:
Dmitry Zuikov 2023-01-22 20:40:53 +03:00
parent 7bac05bfd5
commit 9985ec68de
4 changed files with 94 additions and 45 deletions

View File

@ -17,25 +17,25 @@ newtype HashRef = HashRef (Hash HbSync)
data HashRefObject = HashRefObject HashRef (Maybe HashRefMetadata) data HashRefObject = HashRefObject HashRef (Maybe HashRefMetadata)
deriving stock (Data,Generic) deriving stock (Data,Show,Generic)
newtype HashRefMetadata = newtype HashRefMetadata =
HashRefMetadata HashRef HashRefMetadata HashRef
deriving newtype (Eq,Ord,Pretty) deriving newtype (Eq,Ord,Pretty)
deriving stock (Data,Generic) deriving stock (Data,Show,Generic)
newtype HashRefPrevState = HashRefPrevState HashRef newtype HashRefPrevState = HashRefPrevState HashRef
deriving newtype (Eq,Ord,Pretty,IsString) deriving newtype (Eq,Ord,Pretty,IsString)
deriving stock (Data,Generic) deriving stock (Data,Show,Generic)
data HashRefType = data HashRefType =
HashRefMerkle HashRefObject HashRefMerkle HashRefObject
| HashRefBlob HashRefObject | HashRefBlob HashRefObject
deriving stock (Data,Generic) deriving stock (Data,Show,Generic)
data AnnotatedHashRef = data AnnotatedHashRef =
AnnotatedHashRef (Maybe HashRefPrevState) HashRefType AnnotatedHashRef (Maybe HashRefPrevState) HashRefType
deriving stock (Data,Generic) deriving stock (Data,Show,Generic)
instance Serialise AnnotatedHashRef instance Serialise AnnotatedHashRef

View File

@ -200,9 +200,6 @@ simpleGetBlockLazy :: (IsKey h, Pretty (Key h))
-> IO (Maybe LBS.ByteString) -> IO (Maybe LBS.ByteString)
simpleGetBlockLazy s key = do simpleGetBlockLazy s key = do
liftIO $ print $ "simpleGetBlockLazy" <+> pretty key
resQ <- TBMQ.newTBMQueueIO 1 :: IO (TBMQueue (Maybe LBS.ByteString)) resQ <- TBMQ.newTBMQueueIO 1 :: IO (TBMQueue (Maybe LBS.ByteString))
let fn = simpleBlockFileName s key let fn = simpleBlockFileName s key
let action = do let action = do

View File

@ -254,6 +254,7 @@ blockDownloadLoop = do
processBlock h processBlock h
processBlock h = do processBlock h = do
sto <- getStorage
debug $ "GOT BLOCK!" <+> pretty h debug $ "GOT BLOCK!" <+> pretty h

View File

@ -1,25 +1,5 @@
module Main where module Main where
import Control.Concurrent.Async
import Control.Monad
import Control.Monad.IO.Class
import Control.Monad.Trans.Maybe
import Data.ByteString.Lazy qualified as LBS
import Data.Function
import Data.Functor
import Options.Applicative
import Prettyprinter
import System.Directory
-- import System.FilePath.Posix
import System.IO
import Data.UUID.V4 qualified as UUID
import Data.UUID qualified as UUID
import Codec.Serialise
import Streaming.Prelude qualified as S
-- import Streaming qualified as S
import HBS2.Storage import HBS2.Storage
import HBS2.Storage.Simple import HBS2.Storage.Simple
import HBS2.Storage.Simple.Extra import HBS2.Storage.Simple.Extra
@ -29,6 +9,37 @@ import HBS2.Merkle
import HBS2.Data.Types import HBS2.Data.Types
import HBS2.Defaults import HBS2.Defaults
import Control.Concurrent.Async
import Control.Monad
import Control.Monad.IO.Class
import Control.Monad.Trans.Maybe
import Data.ByteString.Lazy qualified as LBS
import Data.Either
import Data.Function
import Data.Functor
import Data.UUID qualified as UUID
import Data.UUID.V4 qualified as UUID
import Options.Applicative
import Prettyprinter
import System.Directory
import Data.Maybe
-- import System.FilePath.Posix
import System.IO
import System.Exit
import Codec.Serialise
import Streaming.Prelude qualified as S
-- import Streaming qualified as S
newtype CommonOpts =
CommonOpts
{ _coPref :: Maybe StoragePrefix
}
deriving stock (Data)
newtype OptInputFile = OptInputFile { unOptFile :: FilePath } newtype OptInputFile = OptInputFile { unOptFile :: FilePath }
deriving newtype (Eq,Ord,IsString) deriving newtype (Eq,Ord,IsString)
deriving stock (Data) deriving stock (Data)
@ -63,6 +74,10 @@ newtype NewRefOpts =
} }
deriving stock (Data) deriving stock (Data)
data BlobType = Merkle (Hash HbSync)
| AnnRef (Hash HbSync)
| Blob (Hash HbSync)
deriving (Show,Data)
runCat :: Data opts => opts -> SimpleStorage HbSync -> IO () runCat :: Data opts => opts -> SimpleStorage HbSync -> IO ()
runCat opts ss = do runCat opts ss = do
@ -75,24 +90,59 @@ runCat opts ss = do
obj <- MaybeT $ getBlock ss mhash obj <- MaybeT $ getBlock ss mhash
let mbLink = deserialiseOrFail @AnnotatedHashRef obj let mbLink = deserialiseOrFail @AnnotatedHashRef obj >> pure (AnnRef mhash)
let mbMerkle = deserialiseOrFail @(MTree [HashRef]) obj >> pure (Merkle mhash)
let orBlob = Blob mhash
realHash <- MaybeT $ case mbLink of let q = rights [mbLink, mbMerkle] & headDef orBlob
Left _ -> pure $ Just mhash
Right lnk -> do
pure $ headMay [ h
| HashRefMerkle (HashRefObject (HashRef h) _) <- universeBi lnk
]
liftIO $ walkMerkle realHash (getBlock ss) $ \(hr :: [HashRef]) -> do liftIO $ do
forM_ hr $ \(HashRef h) -> do
if honly then do let walk h = walkMerkle h (getBlock ss) $ \(hr :: [HashRef]) -> do
print $ pretty h forM_ hr $ \(HashRef h) -> do
else do if honly then do
mblk <- getBlock ss h print $ pretty h
case mblk of else do
Nothing -> error $ show $ "missed block: " <+> pretty h mblk <- getBlock ss h
Just blk -> LBS.putStr blk case mblk of
Nothing -> die $ show $ "missed block: " <+> pretty h
Just blk -> LBS.putStr blk
case q of
Blob h -> getBlock ss h >>= maybe (die "blob not found") LBS.putStr
Merkle h -> walk h
AnnRef h -> do
let lnk = deserialise @AnnotatedHashRef obj
let mbHead = headMay [ h
| HashRefMerkle (HashRefObject (HashRef h) _) <- universeBi lnk
]
maybe (error "empty ref") walk mbHead
-- case q of
-- Merkle h -> liftIO do
-- walkMerkle h (getBlock ss) $ \(hr :: [HashRef]) -> do
-- forM_ hr $ \(HashRef h) -> do
-- if honly then do
-- print $ pretty h
-- else do
-- mblk <- getBlock ss h
-- case mblk of
-- Nothing -> error $ show $ "missed block: " <+> pretty h
-- Just blk -> LBS.putStr blk
-- case q of
-- realHash <- MaybeT $ case mbLink of
-- Left _ -> pure $ Just mhash
-- Right lnk -> do
-- pure $ headMay [ h
-- | HashRefMerkle (HashRefObject (HashRef h) _) <- universeBi lnk
-- ]
-- -- FIXME: if merkle?
runStore :: Data opts => opts -> SimpleStorage HbSync -> IO () runStore :: Data opts => opts -> SimpleStorage HbSync -> IO ()
@ -155,7 +205,8 @@ main = join . customExecParser (prefs showHelpOnError) $
) )
common = do common = do
pure () pref <- optional $ strOption ( short 'p' <> long "prefix" <> help "storage prefix" )
pure $ CommonOpts pref
pNewRef = do pNewRef = do
o <- common o <- common