This commit is contained in:
Dmitry Zuikov 2024-06-12 08:02:01 +03:00
parent 9ed3377864
commit fd2441c59e
2 changed files with 28 additions and 10 deletions

View File

@ -514,7 +514,7 @@ runForms ss = for_ ss $ \s -> do
deleteFixme hash deleteFixme hash
ListVal [SymbolVal "added", FixmeHashLike _] -> do ListVal [SymbolVal "added", FixmeHashLike _] -> do
-- we dont' add fixmies at that stage -- we don't add fixmies at this stage
-- but in fixme-import -- but in fixme-import
none none
@ -565,22 +565,32 @@ runForms ss = for_ ss $ \s -> do
ListVal [SymbolVal "import-fixmies", StringLike fn] -> do ListVal [SymbolVal "import-fixmies", StringLike fn] -> do
warn $ red "IMPORT-FIXMIES" <+> pretty fn warn $ red "IMPORT-FIXMIES" <+> pretty fn
sto <- compactStorageOpen @HbSync mempty fn
fset <- listAllFixmeHashes
sto <- compactStorageOpen @HbSync readonly fn
ks <- keys sto ks <- keys sto
toImport <- S.toList_ do toImport <- S.toList_ do
for_ ks $ \k -> runMaybeT do for_ ks $ \k -> runMaybeT do
v <- get sto k & MaybeT v <- get sto k & MaybeT
Added _ fx <- deserialiseOrFail @CompactAction (LBS.fromStrict v) & toMPlus what <- deserialiseOrFail @CompactAction (LBS.fromStrict v) & toMPlus
let ha = hashObject @HbSync (serialise fx)
here <- lift $ lift $ checkFixmeExists (HashRef ha) case what of
unless here do Added _ fx -> do
let ha = hashObject @HbSync (serialise fx) & HashRef
unless (HS.member ha fset) do
warn $ red "import" <+> viaShow (pretty ha) warn $ red "import" <+> viaShow (pretty ha)
lift $ S.yield fx lift $ S.yield (Right fx)
w -> lift $ S.yield (Left $ fromRight mempty $ parseTop (show $ pretty w))
withState $ transactional do withState $ transactional do
for_ toImport insertFixme for_ (rights toImport) insertFixme
let w = lefts toImport
runForms (mconcat w)
unless (List.null toImport) do
updateIndexes updateIndexes
compactStorageClose sto compactStorageClose sto

View File

@ -26,6 +26,7 @@ module Fixme.State
, isProcessed , isProcessed
, selectProcessed , selectProcessed
, checkFixmeExists , checkFixmeExists
, listAllFixmeHashes
, HasPredicate(..) , HasPredicate(..)
, SelectPredicate(..) , SelectPredicate(..)
) where ) where
@ -39,6 +40,8 @@ import Data.Config.Suckless
import Data.Config.Suckless.Syntax import Data.Config.Suckless.Syntax
import DBPipe.SQLite hiding (field) import DBPipe.SQLite hiding (field)
import Data.HashSet (HashSet)
import Data.HashSet qualified as HS
import Data.Aeson as Aeson import Data.Aeson as Aeson
import Data.HashMap.Strict qualified as HM import Data.HashMap.Strict qualified as HM
import Text.InterpolatedString.Perl6 (q,qc) import Text.InterpolatedString.Perl6 (q,qc)
@ -441,6 +444,11 @@ selectFixme txt = do
<&> over (field @"fixmeAttr") (<> attrs) <&> over (field @"fixmeAttr") (<> attrs)
listAllFixmeHashes :: (FixmePerks m, MonadReader FixmeEnv m) => m (HashSet HashRef)
listAllFixmeHashes = withState do
select_ @_ @(Only HashRef) [qc|select id from fixme|]
<&> HS.fromList . fmap fromOnly
checkFixmeExists :: FixmePerks m => HashRef -> FixmeM m Bool checkFixmeExists :: FixmePerks m => HashRef -> FixmeM m Bool
checkFixmeExists what = withState do checkFixmeExists what = withState do
select @(Only (Maybe Int)) [qc|select 1 from fixme where id = ? limit 1|] (Only what) select @(Only (Maybe Int)) [qc|select 1 from fixme where id = ? limit 1|] (Only what)