Commit 33a3fc84 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[API][NGRAMS] NgramsId changes and Patch added.

parent 4cd8e9d9
......@@ -115,6 +115,7 @@ library:
- opaleye
- pandoc
- parsec
- patches-map
- path
- path-io
- postgresql-simple
......
......@@ -14,9 +14,7 @@ Ngrams API
-- post :: update NodeNodeNgrams
-- group ngrams
get ngrams filtered by NgramsType
add get
-}
......@@ -30,21 +28,28 @@ add get
module Gargantext.API.Ngrams
where
import GHC.Generics (Generic)
import Data.Aeson (FromJSON, ToJSON)
import Data.Aeson.TH (deriveJSON)
import Data.Map.Strict (Map)
import Data.Map.Strict.Patch (Patch, apply, transformWith)
import Data.Text (Text)
import Gargantext.Prelude
import Data.Set (Set)
import GHC.Generics (Generic)
import Gargantext.Database.Ngram (NgramsId)
import Gargantext.Database.User (UserId)
import Gargantext.Core.Types (ListType(..))
import Gargantext.Core.Types.Main (Tree(..))
import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Core.Types (ListType(..))
import Gargantext.Prelude
data NgramsElement =
NgramsElement { _nn_ngrams :: Text
, _nn_id :: Int
, _nn_list :: ListType
NgramsElement { _ne_id :: Int
, _ne_ngrams :: Text
, _ne_list :: ListType
}
$(deriveJSON (unPrefix "_nn_") ''NgramsElement)
$(deriveJSON (unPrefix "_ne_") ''NgramsElement)
data NgramsTable = NgramsTable { _ngramsTable :: [Tree NgramsElement] }
......@@ -56,6 +61,22 @@ instance FromJSON NgramsTable
instance FromJSON (Tree NgramsElement)
-- TODO
instance ToJSON (Tree NgramsElement)
--data Action = InGroup NgramsId NgramsId
-- | OutGroup NgramsId NgramsId
-- | SetListType NgramsId ListType
data NgramsPatch =
NgramsPatch { list_types :: Map UserId ListType
, add_children :: Set NgramsId
, rem_children :: Set NgramsId
}
data Patch = Map NgramsId NgramsPatch
-- applyPatchBack :: Patch -> IO Patch
-- isEmptyPatch = Map.all (\x -> Set.isEmpty (add_children x) && Set.isEmpty ... )
-------------------------------------------------------------------
-------------------------------------------------------------------
-------------------------------------------------------------------
......@@ -31,10 +31,12 @@ import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
import Data.Text (Text)
import Data.Time (UTCTime)
import GHC.Show(Show(..))
import Gargantext.Database.Node (Cmd(..), mkCmd, runCmd)
import Gargantext.Prelude
import Opaleye
import Gargantext.Prelude
import Gargantext.Database.Node (Cmd(..), mkCmd, runCmd)
------------------------------------------------------------------------
type UserId = Int
data UserLight = UserLight { userLight_id :: Int
......
......@@ -33,6 +33,7 @@ import Data.Maybe (Maybe)
import Data.Text (Text)
import Data.Time.Clock.POSIX (POSIXTime)
import GHC.Generics (Generic)
import Gargantext.Database.Ngram (NgramsId)
import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Prelude
......@@ -53,8 +54,7 @@ type Start = POSIXTime
type End = POSIXTime
-- | Indexed Ngram
type Ngram = (NgramId, Text)
type NgramId = Int
type Ngram = (NgramsId, Text)
-- | PhyloStep : steps of phylomemy on temporal axis
-- Period: tuple (start date, end date) of the step of the phylomemy
......@@ -89,7 +89,7 @@ type PhyloLevelId = (PhyloPeriodId, Int)
data PhyloGroup =
PhyloGroup { _phylo_GroupId :: PhyloGroupId
, _phylo_GroupLabel :: Maybe Text
, _phylo_GroupNgrams :: [NgramId]
, _phylo_GroupNgrams :: [NgramsId]
, _phylo_GroupPeriodParents :: [Edge]
, _phylo_GroupPeriodChilds :: [Edge]
......
......@@ -5,6 +5,7 @@ packages:
- .
- 'deps/servant-job'
- 'deps/clustering-louvain'
- 'deps/patches-map'
#- 'deps/imt-api-client'
allow-newer: true
......
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