Commit fbf08f20 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[API] Upload/new ToSchemas.

parent e58d0f2e
...@@ -55,7 +55,11 @@ instance Arbitrary Query where ...@@ -55,7 +55,11 @@ instance Arbitrary Query where
, fs <- map (map hash) [["a","b"], ["c","d"]] , fs <- map (map hash) [["a","b"], ["c","d"]]
] ]
instance ToSchema Query instance ToSchema Query where
declareNamedSchema =
genericDeclareNamedSchema
defaultSchemaOptions {fieldLabelModifier = \fieldLabel -> drop 6 fieldLabel}
type Api = Summary "New Corpus endpoint" type Api = Summary "New Corpus endpoint"
......
...@@ -27,11 +27,8 @@ module Gargantext.API.Upload ...@@ -27,11 +27,8 @@ module Gargantext.API.Upload
where where
import Control.Lens ((.~), (?~)) import Control.Lens ((.~), (?~))
import qualified Data.Text as Text
import GHC.Generics (Generic)
import Gargantext.Prelude import Gargantext.Prelude
import Data.Text (Text) import Data.Text (Text)
import Data.Aeson
import Data.Monoid import Data.Monoid
import Servant import Servant
import Servant.Multipart import Servant.Multipart
...@@ -86,14 +83,9 @@ instance HasMock (MultipartForm Mem (MultipartData Mem) :> sub) context where ...@@ -86,14 +83,9 @@ instance HasMock (MultipartForm Mem (MultipartData Mem) :> sub) context where
mock _ _ = undefined mock _ _ = undefined
-} -}
data Upload = Upload { up :: [Text] }
deriving (Generic)
instance ToJSON Upload
type Hash = Text type Hash = Text
type ApiUpload = MultipartForm Mem (MultipartData Mem) :> Post '[JSON] Hash type ApiUpload = MultipartForm Mem (MultipartData Mem) :> Post '[JSON] [Hash]
-- MultipartData consists in textual inputs, -- MultipartData consists in textual inputs,
-- accessible through its "inputs" field, as well -- accessible through its "inputs" field, as well
-- as files, accessible through its "files" field. -- as files, accessible through its "files" field.
...@@ -117,7 +109,7 @@ upload multipartData = do ...@@ -117,7 +109,7 @@ upload multipartData = do
-- is <- inputs multipartData -- is <- inputs multipartData
--} --}
pure $ hash $ Text.concat $ map cs is pure $ map (hash . cs) is
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
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