{-|
Module      : Gargantext.Database.Metrics
Description : Get Metrics from Storage (Database like)
Copyright   : (c) CNRS, 2017-Present
License     : AGPL + CECILL v3
Maintainer  : team@gargantext.org
Stability   : experimental
Portability : POSIX

Node API
-}

{-# LANGUAGE QuasiQuotes          #-}
{-# LANGUAGE ScopedTypeVariables  #-}

module Gargantext.Database.Action.Metrics
  where

-- import Gargantext.Database.Action.Metrics.NgramsByContext (refreshNgramsMaterialized)
import Data.HashMap.Strict (HashMap)
import Data.HashMap.Strict qualified as HM
import Data.List qualified as List
import Data.Map.Strict qualified as Map
import Data.Set qualified as Set
import Data.Text qualified as Text
import Data.Vector (Vector)
import Database.PostgreSQL.Simple (Query, Only(..))
import Database.PostgreSQL.Simple.SqlQQ (sql)
import Database.PostgreSQL.Simple.ToField (toField, Action{-, ToField-})
import Database.PostgreSQL.Simple.Types (Values(..), QualifiedIdentifier(..))
import Gargantext.API.Ngrams.Tools (filterListWithRoot, groupNodesByNgrams, Diagonal(..), getCoocByNgrams, mapTermListRoot, RootTerm, getRepo)
import Gargantext.API.Ngrams.Types (TabType(..), ngramsTypeFromTabType, NgramsTerm(..))
import Gargantext.Core (HasDBid(toDBid))
import Gargantext.Core.NodeStory
import Gargantext.Core.Text.Metrics (scored, Scored(..), {-localMetrics, toScored-})
import Gargantext.Core.Types (ListType(..), NodeType(..), ContextId, contextId2NodeId)
import Gargantext.Core.Types.Query (Limit(..))
import Gargantext.Database.Action.Metrics.NgramsByContext (getContextsByNgramsOnlyUser{-, getTficfWith-})
import Gargantext.Database.Admin.Config (userMaster)
import Gargantext.Database.Admin.Types.Node (ListId, CorpusId)
import Gargantext.Database.Prelude
import Gargantext.Database.Query.Table.Node.Select
import Gargantext.Prelude

getMetrics :: NodeStoryEnv err
           -> CorpusId
           -> ListId
           -> TabType
           -> Maybe Limit
           -> DBQuery err x (HashMap NgramsTerm (ListType, Maybe NgramsTerm), Vector (Scored NgramsTerm))
getMetrics env cId listId tabType maybeLimit = do
  (ngs, _, myCooc) <- getNgramsCooc env cId listId tabType maybeLimit
  -- TODO HashMap
  pure (ngs, scored myCooc)


getNgramsCooc :: NodeStoryEnv err
              -> CorpusId
              -> ListId
              -> TabType
              -> Maybe Limit
              -> DBQuery err x ( HashMap NgramsTerm (ListType, Maybe NgramsTerm)
                   , HashMap NgramsTerm (Maybe RootTerm)
                   , HashMap (NgramsTerm, NgramsTerm) Int
                   )
getNgramsCooc env cId lId tabType maybeLimit = do
  (ngs', ngs) <- getNgrams env lId tabType

  lIds <- selectNodesWithUsername NodeList userMaster

  -- FIXME(adn) Audit this, we are converting from a ContextId to a NodeId
  myCooc <- HM.filter (>1) <$> getCoocByNgrams (Diagonal True)
                           <$> HM.map (Set.map contextId2NodeId)
                           <$> groupNodesByNgrams ngs
                           <$> getContextsByNgramsOnlyUser cId
                                                           (lIds <> [lId])
                                                           (ngramsTypeFromTabType tabType)
                                                           (take' maybeLimit $ HM.keys ngs)
  pure $ (ngs', ngs, myCooc)

------------------------------------------------------------------------
------------------------------------------------------------------------
updateNgramsOccurrences :: NodeStoryEnv err
                        -> CorpusId
                        -> ListId
                        -> DBUpdate err ()
updateNgramsOccurrences env cId lId = do
  _ <- mapM (updateNgramsOccurrences' env cId lId Nothing) [Terms, Sources, Authors, Institutes]
  pure ()


updateNgramsOccurrences' :: NodeStoryEnv err
                         -> CorpusId
                         -> ListId
                         -> Maybe Limit
                         -> TabType
                         -> DBUpdate err [Int]
updateNgramsOccurrences' env cId lId maybeLimit tabType = do

  result <- getNgramsOccurrences env cId lId tabType maybeLimit

  let
    toInsert :: [[Action]]
    toInsert =  map (\(ngramsTerm, score)
                        -> [ toField cId
                           , toField lId
                           , toField $ unNgramsTerm ngramsTerm
                           , toField $ toDBid $ ngramsTypeFromTabType tabType
                           , toField score
                           ]
                      )
       $ HM.toList result

    queryInsert :: Query
    queryInsert = [sql|
                  WITH input(corpus_id, list_id, terms, type_id, weight) AS (?)
                  INSERT into node_node_ngrams (node1_id, node2_id, ngrams_id, ngrams_type, weight)
                  SELECT input.corpus_id,input.list_id,ngrams.id,input.type_id,input.weight FROM input
                  JOIN ngrams on ngrams.terms = input.terms
                  ON CONFLICT (node1_id, node2_id, ngrams_id, ngrams_type)
                  DO UPDATE SET weight = excluded.weight
                  RETURNING 1
                  |]

  let fields = map (\t-> QualifiedIdentifier Nothing t)
             $ map Text.pack ["int4", "int4","text","int4","int4"]

  res <- map (\(Only a) -> a) <$> mkPGUpdateReturningMany queryInsert (Only $ Values fields toInsert)

  -- _ <- map (\(Only a) -> a) <$> runPGSQuery [sql|refresh materialized view context_node_ngrams_view;|] ()
  -- _ <- refreshNgramsMaterialized
  pure res



------------------------------------------------------------------------
-- Used for scores in Ngrams Table
getNgramsOccurrences :: NodeStoryEnv err
                     -> CorpusId
                     -> ListId
                     -> TabType
                     -> Maybe Limit
                     -> DBQuery err x (HashMap NgramsTerm Int)
getNgramsOccurrences env c l t ml = HM.map Set.size <$> getNgramsContexts env c l t ml



getNgramsContexts :: NodeStoryEnv err
                  -> CorpusId
                  -> ListId
                  -> TabType
                  -> Maybe Limit
                  -> DBQuery err x (HashMap NgramsTerm (Set ContextId))
getNgramsContexts env cId lId tabType maybeLimit = do
  (_ngs', ngs) <- getNgrams env lId tabType
  lIds <- selectNodesWithUsername NodeList userMaster

  -- TODO maybe add an option to group here
  getContextsByNgramsOnlyUser  cId
                               (lIds <> [lId])
                               (ngramsTypeFromTabType tabType)
                               (take' maybeLimit $ HM.keys ngs)



------------------------------------------------------------------------
updateContextScore :: NodeStoryEnv err
                   -> CorpusId
                   -> ListId
                   -> DBUpdate err [Int]
updateContextScore env cId lId = do

  result <- getContextsNgramsScore env cId lId Terms MapTerm Nothing

  let
    toInsert :: [[Action]]
    toInsert =  map (\(contextId, score)
                        -> [ toField cId
                           , toField contextId
                           , toField score
                           ]
                      )
       $ Map.toList result

    queryInsert :: Query
    queryInsert = [sql|
                  WITH input(node_id, context_id, score) AS (?)
                    UPDATE nodes_contexts nc
                    SET score = input.score
                    FROM input
                    WHERE nc.node_id = input.node_id
                    AND nc.context_id = input.context_id
                    RETURNING 1
                  |]

  let fields = map (\t-> QualifiedIdentifier Nothing t)
             $ map Text.pack ["int4", "int4","int4"]

  map (\(Only a) -> a) <$> mkPGUpdateReturningMany queryInsert (Only $ Values fields toInsert)




-- Used for scores in Doc Table
getContextsNgramsScore :: NodeStoryEnv err
                       -> CorpusId
                       -> ListId
                       -> TabType
                       -> ListType
                       -> Maybe Limit
                       -> DBQuery err x (Map ContextId Int)
getContextsNgramsScore env cId lId tabType listType maybeLimit
 = Map.map Set.size <$> getContextsNgrams env cId lId tabType listType maybeLimit


-- | Given corpus, list, tabType, return a map of contexts to set of
-- ngrams terms
getContextsNgrams :: NodeStoryEnv err
                  -> CorpusId
                  -> ListId
                  -> TabType
                  -> ListType
                  -> Maybe Limit
                  -> DBQuery err x (Map ContextId (Set NgramsTerm))
getContextsNgrams env cId lId tabType listType maybeLimit = do
  (ngs', ngs) <- getNgrams env lId tabType
  lIds <- selectNodesWithUsername NodeList userMaster

  result <- groupNodesByNgrams ngs <$> getContextsByNgramsOnlyUser cId
                                           (lIds <> [lId])
                                           (ngramsTypeFromTabType tabType)
                                           ( take' maybeLimit
                                               $ HM.keys
                                               $ HM.filter (\v -> fst v == listType) ngs'
                                           )

  -- printDebug "getCoocByNgrams" result
  pure $ Map.fromListWith (<>)
       $ List.concat
       $ map (\(ng, contexts) -> List.zip (Set.toList contexts) (List.cycle [Set.singleton ng]))
       $ HM.toList result


------------------------------------------------------------------------
------------------------------------------------------------------------


getNgrams :: NodeStoryEnv err
          -> ListId
          -> TabType
          -> DBQuery err x ( HashMap NgramsTerm (ListType, Maybe NgramsTerm)
               , HashMap NgramsTerm (Maybe RootTerm)
               )
getNgrams env lId tabType = do
  lists <- mapTermListRoot [lId] (ngramsTypeFromTabType tabType) <$> getRepo env [lId]
  -- TODO filterListWithRoot [MapTerm, StopTerm, CandidateTerm] lists
  let maybeSyn = HM.unions $ map (\t -> filterListWithRoot t lists)
                                 [[MapTerm], [StopTerm], [CandidateTerm]]
  pure (lists, maybeSyn)


-- Some useful Tools
take' :: Maybe Limit -> [a] -> [a]
take' Nothing  xs = xs
take' (Just n) xs = take (getLimit n) xs