Commit 5b112d21 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FLOW][DB] completed (todo: many types declared at many places, cleaning it.)

parent 3b01b815
...@@ -141,7 +141,7 @@ instance Arbitrary NgramsPatch where ...@@ -141,7 +141,7 @@ instance Arbitrary NgramsPatch where
-- --
data NgramsIdPatch = data NgramsIdPatch =
NgramsIdPatch { _nip_ngramsId :: NgramsElement NgramsIdPatch { _nip_ngramsId :: NgramsElement
, _nip_ngramsPatch :: NgramsPatch , _nip_ngramsPatch :: NgramsPatch
} }
...@@ -211,11 +211,11 @@ type NgramsIdPatchsBack = NgramsIdPatchs ...@@ -211,11 +211,11 @@ type NgramsIdPatchsBack = NgramsIdPatchs
defaultList :: Connection -> CorpusId -> IO ListId defaultList :: Connection -> CorpusId -> IO ListId
defaultList c cId = view node_id <$> maybe (panic errorMessage) identity defaultList c cId = view node_id <$> maybe (panic noListFound) identity
<$> head <$> head
<$> getListsWithParentId c cId <$> getListsWithParentId c cId
where where
errorMessage = "Gargantext.API.Ngrams.defaultList: no list found" noListFound = "Gargantext.API.Ngrams.defaultList: no list found"
toLists :: ListId -> NgramsIdPatchs -> [(ListId, NgramsId, ListTypeId)] toLists :: ListId -> NgramsIdPatchs -> [(ListId, NgramsId, ListTypeId)]
toLists lId np = map (toList lId) (_nip_ngramsIdPatchs np) toLists lId np = map (toList lId) (_nip_ngramsIdPatchs np)
......
...@@ -80,7 +80,7 @@ corpusTree nId t = TreeN (NodeTree ("Corpus " <> t) NodeCorpus nId) ( [ leafT ...@@ -80,7 +80,7 @@ corpusTree nId t = TreeN (NodeTree ("Corpus " <> t) NodeCorpus nId) ( [ leafT
-- TODO multiple ListType declaration, remove it -- TODO multiple ListType declaration, remove it
data ListType = Stop | Candidate | Map data ListType = Stop | Candidate | Map
deriving (Generic) deriving (Generic, Eq, Ord)
instance ToJSON ListType instance ToJSON ListType
instance FromJSON ListType instance FromJSON ListType
......
...@@ -22,7 +22,7 @@ authors ...@@ -22,7 +22,7 @@ authors
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module Gargantext.Database.Flow module Gargantext.Database.Flow (flowDatabase)
where where
import System.FilePath (FilePath) import System.FilePath (FilePath)
import Data.Maybe (Maybe(..), catMaybes) import Data.Maybe (Maybe(..), catMaybes)
...@@ -48,8 +48,8 @@ type UserId = Int ...@@ -48,8 +48,8 @@ type UserId = Int
type RootId = Int type RootId = Int
type CorpusId = Int type CorpusId = Int
flow :: FilePath -> CorpusName -> IO [Int] flowDatabase :: FilePath -> CorpusName -> IO [Int]
flow fp cName = do flowDatabase fp cName = do
-- Corus Flow -- Corus Flow
(masterUserId, _, corpusId) <- subFlow "gargantua" "Big Corpus" (masterUserId, _, corpusId) <- subFlow "gargantua" "Big Corpus"
...@@ -209,8 +209,9 @@ insertGroups lId ngrs = ...@@ -209,8 +209,9 @@ insertGroups lId ngrs =
] ]
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- TODO: verify NgramsT lost here
ngrams2list :: Map (NgramsT NgramsIndexed) (Map NodeId Int) -> Map ListType NgramsIndexed ngrams2list :: Map (NgramsT NgramsIndexed) (Map NodeId Int) -> Map ListType NgramsIndexed
ngrams2list = undefined ngrams2list = DM.fromList . zip (repeat Candidate) . map (\(NgramsT t ng) -> ng) . DM.keys
-- | TODO: weight of the list could be a probability -- | TODO: weight of the list could be a probability
insertLists :: ListId -> Map ListType NgramsIndexed -> Cmd Int insertLists :: ListId -> Map ListType NgramsIndexed -> Cmd Int
......
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