List.hs 4.04 KB
Newer Older
1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17
{-|
Module      : Gargantext.API.Ngrams.List
Description : Get Ngrams (lists)
Copyright   : (c) CNRS, 2017-Present
License     : AGPL + CECILL v3
Maintainer  : team@gargantext.org
Stability   : experimental
Portability : POSIX

-}

{-# LANGUAGE TemplateHaskell   #-}
{-# LANGUAGE TypeOperators     #-}

module Gargantext.API.Ngrams.List
  where

18
import Control.Lens hiding (elements)
19
import Data.Aeson
20
import Data.Map (Map, toList, fromList)
21 22 23
import Data.Swagger (ToSchema, declareNamedSchema, genericDeclareNamedSchema)
import Data.Text (Text, concat, pack)
import GHC.Generics (Generic)
24 25 26 27 28 29 30
import Network.HTTP.Media ((//), (/:))
import Servant
import Servant.Job.Async
import Servant.Job.Utils (jsonOptions)
import Web.FormUrlEncoded (FromForm)

import Gargantext.Prelude
31
import Gargantext.API.Node.Corpus.New.File (FileType(..))
32
import Gargantext.API.Ngrams
33
import Gargantext.API.Admin.Orchestrator.Types
34
import Gargantext.API.Prelude (GargServer)
35
import Gargantext.Core.Utils.Prefix (unPrefixSwagger)
36 37 38
import Gargantext.Database.Action.Flow (FlowCmdM)
import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Schema.Ngrams (NgramsType(..), ngramsTypes)
39

40
------------------------------------------------------------------------
41
type NgramsList = (Map NgramsType (Versioned NgramsTableMap))
42
------------------------------------------------------------------------
43
type API =  Get '[JSON, HTML] (Headers '[Header "Content-Disposition" Text] NgramsList)
44 45 46 47
       -- :<|> ReqBody '[JSON] NgramsList :> Post '[JSON] Bool
       :<|> PostAPI

api :: ListId -> GargServer API
48
api l = get l :<|> postAsync l
49

50 51 52 53 54 55
data HTML
instance Accept HTML where
  contentType _ = "text" // "html" /: ("charset", "utf-8")
instance ToJSON a => MimeRender HTML a where
  mimeRender _ = encode

56
------------------------------------------------------------------------
57 58
get :: RepoCmdM env err m =>
       ListId -> m (Headers '[Header "Content-Disposition" Text] NgramsList)
59 60 61 62 63 64 65 66 67 68
get lId = do
  lst <- get' lId
  let (NodeId id) = lId
  return $ addHeader (concat [ "attachment; filename=GarganText_NgramsList-"
                             , pack $ show id
                             , ".json"
                             ]
                     ) lst

get' :: RepoCmdM env err m
69
    => ListId -> m NgramsList
70
get' lId = fromList
71 72 73
       <$> zip ngramsTypes
       <$> mapM (getNgramsTableMap lId) ngramsTypes

74
------------------------------------------------------------------------
75
-- TODO : purge list
76
-- TODO talk
77
post :: FlowCmdM env err m
78 79 80
    => ListId
    -> NgramsList
    -> m Bool
81
post l m  = do
82
  -- TODO check with Version for optim
83
  _ <- mapM (\(nt, Versioned _v ns) -> setListNgrams l nt ns) $ toList m
84
  -- TODO reindex
85 86
  pure True

87 88 89 90 91 92
------------------------------------------------------------------------
------------------------------------------------------------------------
type PostAPI = Summary "Update List"
        :> "add"
        :> "form"
        :> "async"
93
        :> AsyncJobs JobLog '[FormUrlEncoded] WithFile JobLog
94 95 96 97

postAsync :: ListId -> GargServer PostAPI
postAsync lId =
  serveJobsAPI $
98
    JobFunction (\f  log' -> postAsync' lId f (liftBase . log'))
99 100 101 102

postAsync' :: FlowCmdM env err m
          => ListId
          -> WithFile
103 104
          -> (JobLog -> m ())
          -> m JobLog
105 106
postAsync' l (WithFile _ m _) logStatus = do

107
  logStatus JobLog { _scst_succeeded = Just 0
108 109 110 111
                   , _scst_failed    = Just 0
                   , _scst_remaining = Just 1
                   , _scst_events    = Just []
                   }
112 113
  _r <- post l m

114
  pure JobLog { _scst_succeeded = Just 1
115 116 117 118
              , _scst_failed    = Just 0
              , _scst_remaining = Just 0
              , _scst_events    = Just []
              }
119 120 121 122 123 124 125 126 127 128 129 130 131

data WithFile = WithFile
  { _wf_filetype :: !FileType
  , _wf_data     :: !NgramsList
  , _wf_name     :: !Text
  } deriving (Eq, Show, Generic)

makeLenses ''WithFile
instance FromForm WithFile
instance FromJSON WithFile where
  parseJSON = genericParseJSON $ jsonOptions "_wf_"
instance ToSchema WithFile where
  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_wf_")
132