This commit is contained in:
Dmitry Zuikov 2024-06-14 12:06:15 +03:00
parent fed1845ec8
commit 20360a2180
3 changed files with 33 additions and 5 deletions

1
.gitignore vendored
View File

@ -12,3 +12,4 @@ cabal.project.local
.backup/ .backup/
.hbs2-git/ .hbs2-git/
bin/ bin/
.fixme-new/current-stage.log

View File

@ -747,11 +747,14 @@ runForms ss = for_ ss $ \s -> do
fxm <- gitExtractFileMetaData fs <&> HM.toList fxm <- gitExtractFileMetaData fs <&> HM.toList
liftIO $ print $ vcat (fmap (pretty.snd) fxm) liftIO $ print $ vcat (fmap (pretty.snd) fxm)
ListVal [SymbolVal "builtin:extract-from-stage"] -> do ListVal (SymbolVal "builtin:git:extract-from-stage" : opts) -> do
env <- ask env <- ask
stage <- gitListStage gitStage <- gitListStage
blobs <- for stage $ \case let dry = or [ True | StringLike "dry" <- opts ]
let verbose = or [ True | StringLike "verbose" <- opts ]
blobs <- for gitStage $ \case
Left (fn, hash) -> pure (fn, hash, liftIO $ LBS8.readFile fn) Left (fn, hash) -> pure (fn, hash, liftIO $ LBS8.readFile fn)
Right (fn,hash) -> pure (fn, hash, liftIO (withFixmeEnv env $ gitCatBlob hash)) Right (fn,hash) -> pure (fn, hash, liftIO (withFixmeEnv env $ gitCatBlob hash))
@ -760,6 +763,10 @@ runForms ss = for_ ss $ \s -> do
-- TODO: extract-metadata-from-git-blame -- TODO: extract-metadata-from-git-blame
-- subj -- subj
stageFile <- localConfigDir <&> (</> "current-stage.log")
fmeStage <- compactStorageOpen mempty stageFile
for_ blobs $ \(fn, bhash, readBlob) -> do for_ blobs $ \(fn, bhash, readBlob) -> do
nno <- newTVarIO (mempty :: HashMap FixmeTitle Integer) nno <- newTVarIO (mempty :: HashMap FixmeTitle Integer)
lbs <- readBlob lbs <- readBlob
@ -788,9 +795,22 @@ runForms ss = for_ ss $ \s -> do
& over (field @"fixmeAttr") & over (field @"fixmeAttr")
(mappend (kh<>kv)) (mappend (kh<>kv))
for_ fxs $ \fx -> do unless dry do
for_ fxs $ \fx -> void $ runMaybeT do
e <- getEpoch
let what = Added e fx
let k = mkKey (FromFixmeKey fx)
get fmeStage k >>= guard . isNothing
put fmeStage k (LBS.toStrict $ serialise what)
when verbose do
liftIO $ print (pretty fx) liftIO $ print (pretty fx)
when dry do
warn $ red "FUCKING DRY!"
compactStorageClose fmeStage
ListVal [SymbolVal "trace"] -> do ListVal [SymbolVal "trace"] -> do
setLogging @TRACE (logPrefix "[trace] " . toStderr) setLogging @TRACE (logPrefix "[trace] " . toStderr)
trace "trace on" trace "trace on"

View File

@ -220,6 +220,8 @@ data SimpleTemplate = forall c . (IsContext c, Data (Context c), Data c) => Simp
class HasSequence w where class HasSequence w where
getSequence :: w -> Word64 getSequence :: w -> Word64
newtype FromFixmeKey a = FromFixmeKey a
data CompactAction = data CompactAction =
Deleted Word64 HashRef Deleted Word64 HashRef
| Modified Word64 HashRef FixmeAttrName FixmeAttrVal | Modified Word64 HashRef FixmeAttrName FixmeAttrVal
@ -234,6 +236,11 @@ instance MkKey CompactAction where
mkKey (Modified _ h _ _) = "M" <> LBS.toStrict (serialise h) mkKey (Modified _ h _ _) = "M" <> LBS.toStrict (serialise h)
mkKey (Added _ fixme) = "A" <> coerce (hashObject @HbSync $ serialise fixme) mkKey (Added _ fixme) = "A" <> coerce (hashObject @HbSync $ serialise fixme)
instance MkKey (FromFixmeKey Fixme) where
mkKey (FromFixmeKey fx@Fixme{..}) =
maybe k2 (mappend "A" . LBS.toStrict . serialise) (HM.lookup "fixme-key" fixmeAttr)
where k2 = mappend "A" $ serialise fx & LBS.toStrict
instance Pretty CompactAction where instance Pretty CompactAction where
pretty = \case pretty = \case
Deleted s r -> pretty $ mklist @C [ mksym "deleted", mkint s, mkstr r ] Deleted s r -> pretty $ mklist @C [ mksym "deleted", mkint s, mkstr r ]