Commit a0c61ebe authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FIX] User History of patches, ok

parent 9b35cefd
Pipeline #1288 canceled with stage
......@@ -644,7 +644,7 @@ data Repo s p = Repo
, _r_history :: ![p]
-- first patch in the list is the most recent
}
deriving (Generic)
deriving (Generic, Show)
instance (FromJSON s, FromJSON p) => FromJSON (Repo s p) where
parseJSON = genericParseJSON $ unPrefix "_r_"
......
......@@ -11,7 +11,6 @@ Portability : POSIX
module Gargantext.Core.Text.List.Social.History
where
import Data.Maybe (catMaybes)
import Data.Map (Map)
import Control.Lens (view)
import Gargantext.API.Ngrams.Types
......@@ -23,22 +22,39 @@ import qualified Data.List as List
import Gargantext.Database.Schema.Ngrams (NgramsType(..))
userHistory :: [NgramsType]
-> [ListId]
-> Repo s NgramsStatePatch
-> Map NgramsType (Map ListId [Map NgramsTerm NgramsPatch])
userHistory t l r = clean $ history t l r
where
clean = Map.map (Map.map List.init)
history :: (Foldable t, Foldable h)
=> t NgramsType
-> h ListId
history :: [NgramsType]
-> [ListId]
-> Repo s NgramsStatePatch
-> Map NgramsType (Map ListId [Map NgramsTerm NgramsPatch])
history types lists = Map.unionsWith (<>)
. map (Map.map (Map.map cons))
. map (Map.map ((Map.filterWithKey (\k _ -> List.elem k lists))))
. map (Map.filterWithKey (\k _ -> List.elem k types))
. map toMap
. view r_history
history types lists = merge
. map (Map.map ( Map.map cons))
. map (Map.map ((Map.filterWithKey (\k _ -> List.elem k lists))))
. map (Map.filterWithKey (\k _ -> List.elem k types))
. map toMap
. view r_history
where
cons a = [a]
merge :: [Map NgramsType (Map ListId [Map NgramsTerm NgramsPatch])]
-> Map NgramsType (Map ListId [Map NgramsTerm NgramsPatch])
merge = Map.unionsWith merge'
where
merge' :: Map ListId [Map NgramsTerm NgramsPatch]
-> Map ListId [Map NgramsTerm NgramsPatch]
-> Map ListId [Map NgramsTerm NgramsPatch]
merge' = Map.unionWith (<>)
toMap :: PatchMap NgramsType
(PatchMap NodeId
(NgramsTablePatch
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment