Small refactoring to have less hard-coded Lang

parent 45cddcc1
Pipeline #296 canceled with stage
......@@ -104,16 +104,16 @@ flowCorpus :: (FlowCmdM env ServantErr m, ToHyperdataDocument a)
=> Username -> CorpusName -> TermType Lang -> [[a]] -> m CorpusId
flowCorpus u cn la docs = do
ids <- mapM ((insertMasterDocs la) . (map toHyperdataDocument)) docs
flowCorpusUser FR u cn (concat ids)
flowCorpusUser (la ^. tt_lang) u cn (concat ids)
-- TODO query with complex query
flowCorpusSearchInDatabase :: FlowCmdM env ServantErr m
=> Username -> Text -> m CorpusId
flowCorpusSearchInDatabase u q = do
=> Username -> Text -> Lang -> m CorpusId
flowCorpusSearchInDatabase u la q = do
(_masterUserId, _masterRootId, cId) <- getOrMkRootWithCorpus userMaster ""
ids <- map fst <$> searchInDatabase cId (stemIt q)
flowCorpusUser FR u q ids
flowCorpusUser la u q ids
flowCorpusUser :: FlowCmdM env ServantErr m
......
......@@ -29,10 +29,12 @@ compute graph
-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Text.Terms
where
import Control.Lens
import Data.Text (Text)
import Data.Traversable
......@@ -43,8 +45,12 @@ import Gargantext.Text.Terms.Multi (multiterms)
import Gargantext.Text.Terms.Mono (monoTerms)
data TermType lang = Mono lang | Multi lang | MonoMulti lang
data TermType lang
= Mono { _tt_lang :: lang }
| Multi { _tt_lang :: lang }
| MonoMulti { _tt_lang :: lang }
makeLenses ''TermType
--group :: [Text] -> [Text]
--group = undefined
......
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