1 {-# LANGUAGE DataKinds #-}
2 {-# LANGUAGE TemplateHaskell #-}
3 {-# LANGUAGE TypeOperators #-}
4 module Data.Gargantext.Server
10 import Control.Concurrent
12 import Control.Monad.IO.Class
15 import Data.Gargantext.Types
16 import Network.HTTP.Client.MultipartFormData
18 import Network.Wai.Handler.Warp
20 import Servant.Multipart
22 -- | TODO, use MOCK feature of Servant to generate fake data (for tests)
24 data FakeNode = FakeNode
26 , fakeNodeName :: String
29 $(deriveJSON defaultOptions ''FakeNode)
31 type API = "nodes" :> Get '[JSON] [FakeNode]
32 :<|> "node" :> Capture "id" Int :> Get '[JSON] FakeNode
33 :<|> "echo" :> Capture "string" String :> Get '[JSON] String
34 :<|> "upload" :> MultipartForm MultipartData :> Post '[JSON] String
36 -- :<|> "node" :> Capture "id" Int :> Get '[JSON] Node
39 server = pure fakeNodes
47 startGargantext :: IO ()
48 startGargantext = print ("Starting server on port " ++ show port) >> run port app
52 -- | TODO App type, the main monad in which the bot code is written with.
53 -- Provide config, state, logs and IO
54 -- type App m a = ( MonadState AppState m
55 -- , MonadReader Conf m
56 -- , MonadLog (WithSeverity Doc) m
57 -- , MonadIO m) => m a
58 -- Thanks @yannEsposito for this.
60 app = serve api server
66 fakeNode :: Monad m => Int -> m FakeNode
67 fakeNode id = pure (fakeNodes !! id)
69 fakeNodes :: [FakeNode]
70 fakeNodes = [ FakeNode 1 "Poincare"
71 , FakeNode 2 "Grothendieck"
75 -- TODO Is it possible to adapt the function according to iValue input ?
76 upload :: MultipartData -> Handler String
77 upload multipartData = do
80 forM_ (inputs multipartData) $ \input ->
81 putStrLn $ " " ++ show (iName input)
82 ++ " -> " ++ show (iValue input)
84 forM_ (files multipartData) $ \file -> do
85 content <- readFile (fdFilePath file)
86 putStrLn $ "Content of " ++ show (fdFileName file)
87 ++ " at " ++ fdFilePath file