2 Module : Gargantext.API.Node.Corpus.New.File
3 Description : Server API
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
12 {-# OPTIONS_GHC -fno-warn-orphans #-}
14 {-# LANGUAGE ScopedTypeVariables #-}
15 {-# LANGUAGE TemplateHaskell #-}
16 {-# LANGUAGE TypeOperators #-}
18 module Gargantext.API.Node.Corpus.New.File
21 import Control.Lens ((.~), (?~))
22 import Control.Monad (forM)
24 import Data.Monoid (mempty)
26 import Data.Text (Text())
29 import Servant.Multipart
30 import Servant.Swagger.Internal
32 import Gargantext.API.Node.Corpus.New.Types
33 import Gargantext.Core.Types (TODO)
34 import Gargantext.Database.Admin.Types.Node
35 import Gargantext.Database.Prelude -- (Cmd, CmdM)
36 import Gargantext.Prelude
37 import Gargantext.Prelude.Crypto.Hash (hash)
39 -------------------------------------------------------------
42 instance ToParamSchema (MultipartData Mem) where toParamSchema _ = toParamSchema (Proxy :: Proxy TODO)
44 instance (ToParamSchema a, HasSwagger sub) =>
45 HasSwagger (MultipartForm tag a :> sub) where
47 toSwagger _ = toSwagger (Proxy :: Proxy sub)
52 & schema .~ ParamOther sch
54 & in_ .~ ParamFormData
55 & paramSchema .~ toParamSchema (Proxy :: Proxy a)
58 type WithUpload' = Summary "Upload file(s) to a corpus"
59 :> QueryParam "fileType" FileType
60 :> QueryParam "fileFormat" FileFormat
61 :> MultipartForm Mem (MultipartData Mem)
62 :> Post '[JSON] [Hash]
64 --postUpload :: NodeId -> Maybe FileType -> GargServer UploadAPI
65 --postUpload :: NodeId -> GargServer UploadAPI
71 postUpload _ Nothing _ _ = panic "fileType is a required parameter"
72 postUpload _ _ Nothing _ = panic "fileFormat is a required parameter"
73 postUpload _ (Just _fileType) (Just _fileFormat) multipartData = do
74 -- printDebug "File Type: " fileType
75 -- printDebug "File format: " fileFormat
77 -- printDebug "Inputs:" ()
78 forM (inputs multipartData) $ \input -> do
79 -- printDebug "iName " (iName input)
80 -- printDebug "iValue " (iValue input)
84 _ <- forM (files multipartData) $ \file -> do
85 -- let content = fdPayload file
86 -- printDebug "XXX " (fdFileName file)
87 -- printDebug "YYY " content
88 pure () -- $ cs content
89 -- is <- inputs multipartData
93 -------------------------------------------------------------------