]> Git — Sourcephile - gargantext.git/blob - src/Data/Gargantext/Server.hs
First commit to start with.
[gargantext.git] / src / Data / Gargantext / Server.hs
1 {-# LANGUAGE DataKinds #-}
2 {-# LANGUAGE TemplateHaskell #-}
3 {-# LANGUAGE TypeOperators #-}
4 module Data.Gargantext.Server
5 -- ( startApp
6 -- , app
7 -- )
8 where
9
10 import Control.Concurrent
11 import Control.Monad
12 import Control.Monad.IO.Class
13 import Data.Aeson
14 import Data.Aeson.TH
15 import Data.Gargantext.Types
16 import Network.HTTP.Client.MultipartFormData
17 import Network.Wai
18 import Network.Wai.Handler.Warp
19 import Servant
20 import Servant.Multipart
21
22 -- | TODO, use MOCK feature of Servant to generate fake data (for tests)
23
24 data FakeNode = FakeNode
25 { fakeNodeId :: Int
26 , fakeNodeName :: String
27 } deriving (Eq, Show)
28
29 $(deriveJSON defaultOptions ''FakeNode)
30
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
35
36 -- :<|> "node" :> Capture "id" Int :> Get '[JSON] Node
37
38 server :: Server API
39 server = pure fakeNodes
40 :<|> fakeNode
41 :<|> echo
42 :<|> upload
43 where
44 echo s = pure s
45
46
47 startGargantext :: IO ()
48 startGargantext = print ("Starting server on port " ++ show port) >> run port app
49 where
50 port = 8008
51
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.
59 app :: Application
60 app = serve api server
61
62 api :: Proxy API
63 api = Proxy
64
65
66 fakeNode :: Monad m => Int -> m FakeNode
67 fakeNode id = pure (fakeNodes !! id)
68
69 fakeNodes :: [FakeNode]
70 fakeNodes = [ FakeNode 1 "Poincare"
71 , FakeNode 2 "Grothendieck"
72 ]
73
74 -- | Upload files
75 -- TODO Is it possible to adapt the function according to iValue input ?
76 upload :: MultipartData -> Handler String
77 upload multipartData = do
78 liftIO $ do
79 putStrLn "Inputs:"
80 forM_ (inputs multipartData) $ \input ->
81 putStrLn $ " " ++ show (iName input)
82 ++ " -> " ++ show (iValue input)
83
84 forM_ (files multipartData) $ \file -> do
85 content <- readFile (fdFilePath file)
86 putStrLn $ "Content of " ++ show (fdFileName file)
87 ++ " at " ++ fdFilePath file
88 putStrLn content
89 pure "Data loaded"
90
91
92
93