Commit 2562402a authored by Nicolas Pouillard's avatar Nicolas Pouillard

NodeAPI /roots, /node

parent 277e24b4
...@@ -19,14 +19,14 @@ import Database.PostgreSQL.Simple.Internal (Field) ...@@ -19,14 +19,14 @@ import Database.PostgreSQL.Simple.Internal (Field)
import Control.Arrow (returnA) import Control.Arrow (returnA)
import Control.Lens.TH (makeLensesWith, abbreviatedFields) import Control.Lens.TH (makeLensesWith, abbreviatedFields)
import Data.Aeson import Data.Aeson
import Data.Gargantext.Database.Private (infoGargandb)
import Data.Gargantext.Types import Data.Gargantext.Types
import Data.Maybe (Maybe) import Data.Gargantext.Prelude
import Data.Maybe (Maybe, fromMaybe)
import Data.Text (Text) import Data.Text (Text)
import Data.Profunctor.Product.TH (makeAdaptorAndInstance) import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
import Data.Typeable (Typeable) import Data.Typeable (Typeable)
import qualified Data.ByteString.Internal as DBI import qualified Data.ByteString.Internal as DBI
import qualified Database.PostgreSQL.Simple as PGS import Database.PostgreSQL.Simple (Connection)
import Opaleye import Opaleye
-- | Types for Node Database Management -- | Types for Node Database Management
...@@ -105,13 +105,13 @@ nodeTable = Table "nodes" (pNode Node { node_id = optional "id" ...@@ -105,13 +105,13 @@ nodeTable = Table "nodes" (pNode Node { node_id = optional "id"
) )
selectNodes :: Column PGInt4 -> Query (Column (PGText)) selectNodes :: Column PGInt4 -> Query NodeRead
selectNodes node_id = proc () -> do selectNodes id = proc () -> do
(Node n_id _tn _u _p n _d _h ) <- queryNodeTable -< () row <- queryNodeTable -< ()
restrict -< n_id .== node_id restrict -< node_id row .== id
returnA -< n returnA -< row
runGetNodes :: PGS.Connection -> Query NodeRead -> IO [Document] runGetNodes :: Connection -> Query NodeRead -> IO [Document]
runGetNodes = runQuery runGetNodes = runQuery
...@@ -122,6 +122,7 @@ queryNodeTable = queryTable nodeTable ...@@ -122,6 +122,7 @@ queryNodeTable = queryTable nodeTable
selectNodeWithParentID :: Column (Nullable PGInt4) -> Query NodeRead selectNodeWithParentID :: Column (Nullable PGInt4) -> Query NodeRead
selectNodeWithParentID node_id = proc () -> do selectNodeWithParentID node_id = proc () -> do
row@(Node _id _tn _u p_id _n _d _h) <- queryNodeTable -< () row@(Node _id _tn _u p_id _n _d _h) <- queryNodeTable -< ()
-- restrict -< maybe (isNull p_id) (p_id .==) node_id
restrict -< p_id .== node_id restrict -< p_id .== node_id
returnA -< row returnA -< row
...@@ -129,25 +130,26 @@ selectNodesWithType :: Column PGInt4 -> Query NodeRead ...@@ -129,25 +130,26 @@ selectNodesWithType :: Column PGInt4 -> Query NodeRead
selectNodesWithType type_id = proc () -> do selectNodesWithType type_id = proc () -> do
row@(Node _ tn _ _ _ _ _) <- queryNodeTable -< () row@(Node _ tn _ _ _ _ _) <- queryNodeTable -< ()
restrict -< tn .== type_id restrict -< tn .== type_id
--let noParent = ifThenElse (isNull nullableBoss) (pgString "no") (pgString "a")
--returnA -< Node _id _tn _uid (pgInt4 0) (pgString "") _d _h
returnA -< row returnA -< row
getNodesWithType :: Column PGInt4 -> IO [NodeUser] getNode :: Connection -> Column PGInt4 -> IO (Node Value)
getNodesWithType type_id = do getNode conn id = do
conn <- PGS.connect infoGargandb fromMaybe (error "TODO: 404") . headMay <$> runQuery conn (limit 1 $ selectNodes id)
getNodesWithType :: Connection -> Column PGInt4 -> IO [Node Value]
getNodesWithType conn type_id = do
runQuery conn $ selectNodesWithType type_id runQuery conn $ selectNodesWithType type_id
getNodesWithParentId :: Column (Nullable PGInt4) -> IO [Document] -- NP check type
getNodesWithParentId node_id = do getNodesWithParentId :: Connection -> Column (Nullable PGInt4) -> IO [Node Value]
conn <- PGS.connect infoGargandb getNodesWithParentId conn node_id = do
runQuery conn $ selectNodeWithParentID node_id runQuery conn $ selectNodeWithParentID node_id
getCorpusDocument :: Column (Nullable PGInt4) -> IO [Document] -- NP check type
getCorpusDocument node_id = PGS.connect infoGargandb >>= getCorpusDocument :: Connection -> Column PGInt4 -> IO [Document]
\conn -> runQuery conn (selectNodeWithParentID node_id) getCorpusDocument conn node_id = runQuery conn (selectNodeWithParentID $ toNullable node_id)
getProjectCorpora :: Column (Nullable PGInt4) -> IO [Corpus] -- NP check type
getProjectCorpora node_id = do getProjectCorpora :: Connection -> Column (Nullable PGInt4) -> IO [Corpus]
conn <- PGS.connect infoGargandb getProjectCorpora conn node_id = do
runQuery conn $ selectNodeWithParentID node_id runQuery conn $ selectNodeWithParentID node_id
...@@ -53,6 +53,10 @@ import Safe (headMay) ...@@ -53,6 +53,10 @@ import Safe (headMay)
-- | Final Date parser API -- | Final Date parser API
-- IO can be avoided here:
-- currentContext :: Lang -> IO Context
-- currentContext lang = localContext lang <$> utcToDucklingTime <$> getCurrentTime
-- parseDate1 :: Context -> Text -> SomeErrorHandling Text
parseDate1 :: Lang -> Text -> IO Text parseDate1 :: Lang -> Text -> IO Text
parseDate1 lang text = do parseDate1 lang text = do
maybeJson <- pm jsonValue <$> parseDateWithDuckling lang text maybeJson <- pm jsonValue <$> parseDateWithDuckling lang text
......
...@@ -6,7 +6,12 @@ ...@@ -6,7 +6,12 @@
TODO: import head impossible from Protolude: why ? TODO: import head impossible from Protolude: why ?
-} -}
module Data.Gargantext.Prelude where module Data.Gargantext.Prelude
( module Data.Gargantext.Prelude
, module Protolude
, headMay
)
where
import Protolude ( Bool(True, False), Int, Double, Integer import Protolude ( Bool(True, False), Int, Double, Integer
, Fractional, Num, Maybe, Floating, Char , Fractional, Num, Maybe, Floating, Char
...@@ -26,7 +31,7 @@ import qualified Data.List as L hiding (head, sum) ...@@ -26,7 +31,7 @@ import qualified Data.List as L hiding (head, sum)
import qualified Control.Monad as M import qualified Control.Monad as M
import qualified Data.Map as Map import qualified Data.Map as Map
import qualified Data.Vector as V import qualified Data.Vector as V
-- import Safe (headMay) import Safe (headMay)
pf :: (a -> Bool) -> [a] -> [a] pf :: (a -> Bool) -> [a] -> [a]
......
...@@ -8,34 +8,37 @@ module Data.Gargantext.Server ...@@ -8,34 +8,37 @@ module Data.Gargantext.Server
-- ) -- )
where where
import Prelude hiding (null)
import Control.Monad import Control.Monad
import Control.Monad.IO.Class import Control.Monad.IO.Class
import Data.Aeson import Data.Aeson
import Data.Aeson.TH
import Network.Wai import Network.Wai
import Network.Wai.Handler.Warp import Network.Wai.Handler.Warp
import Servant import Servant
import Servant.Multipart import Servant.Multipart
import Database.PostgreSQL.Simple (Connection, connect)
import Opaleye
-- | TODO, use MOCK feature of Servant to generate fake data (for tests) import Data.Gargantext.Types.Main (Node, NodeId)
import Data.Gargantext.Database.Node (getNodesWithParentId, getNode)
import Data.Gargantext.Database.Private (infoGargandb)
data FakeNode = FakeNode -- | TODO, use MOCK feature of Servant to generate fake data (for tests)
{ fakeNodeId :: Int
, fakeNodeName :: String
} deriving (Eq, Show)
$(deriveJSON defaultOptions ''FakeNode) type NodeAPI = Get '[JSON] (Node Value)
:<|> "children" :> Get '[JSON] [Node Value]
type API = "nodes" :> Get '[JSON] [FakeNode] type API = "roots" :> Get '[JSON] [Node Value]
:<|> "node" :> Capture "id" Int :> Get '[JSON] FakeNode :<|> "node" :> Capture "id" Int :> NodeAPI
:<|> "echo" :> Capture "string" String :> Get '[JSON] String :<|> "echo" :> Capture "string" String :> Get '[JSON] String
:<|> "upload" :> MultipartForm MultipartData :> Post '[JSON] String :<|> "upload" :> MultipartForm MultipartData :> Post '[JSON] String
-- :<|> "node" :> Capture "id" Int :> Get '[JSON] Node -- :<|> "node" :> Capture "id" Int :> Get '[JSON] Node
server :: Server API server :: Connection -> Server API
server = pure fakeNodes server conn
:<|> fakeNode = liftIO (getNodesWithParentId conn null)
:<|> nodeAPI conn
:<|> echo :<|> echo
:<|> upload :<|> upload
where where
...@@ -43,7 +46,10 @@ server = pure fakeNodes ...@@ -43,7 +46,10 @@ server = pure fakeNodes
startGargantext :: IO () startGargantext :: IO ()
startGargantext = print ("Starting server on port " ++ show port) >> run port app startGargantext = do
print ("Starting server on port " ++ show port)
conn <- connect infoGargandb
run port $ app conn
where where
port = 8008 port = 8008
...@@ -54,20 +60,17 @@ startGargantext = print ("Starting server on port " ++ show port) >> run port a ...@@ -54,20 +60,17 @@ startGargantext = print ("Starting server on port " ++ show port) >> run port a
-- , MonadLog (WithSeverity Doc) m -- , MonadLog (WithSeverity Doc) m
-- , MonadIO m) => m a -- , MonadIO m) => m a
-- Thanks @yannEsposito for this. -- Thanks @yannEsposito for this.
app :: Application app :: Connection -> Application
app = serve api server app = serve api . server
api :: Proxy API api :: Proxy API
api = Proxy api = Proxy
nodeAPI :: Connection -> NodeId -> Server NodeAPI
fakeNode :: Monad m => Int -> m FakeNode nodeAPI conn id
fakeNode id = pure (fakeNodes !! id) = liftIO (getNode conn id')
:<|> liftIO (getNodesWithParentId conn (toNullable id'))
fakeNodes :: [FakeNode] where id' = pgInt4 id
fakeNodes = [ FakeNode 1 "Poincare"
, FakeNode 2 "Grothendieck"
]
-- | Upload files -- | Upload files
-- TODO Is it possible to adapt the function according to iValue input ? -- TODO Is it possible to adapt the function according to iValue input ?
......
...@@ -33,34 +33,43 @@ data Language = EN | FR -- | DE | IT | SP ...@@ -33,34 +33,43 @@ data Language = EN | FR -- | DE | IT | SP
-- All the Database is structred like a hierarchical Tree -- All the Database is structred like a hierarchical Tree
data Tree b a = LeafT a | NodeT b [Tree b a] data Tree a = NodeT a [Tree a]
deriving (Show, Read, Eq) deriving (Show, Read, Eq)
-- data Tree a = NodeT a [Tree a]
-- same as Data.Tree
leafT :: a -> Tree a
leafT x = NodeT x []
-- Garg Network is a network of all Garg nodes -- Garg Network is a network of all Garg nodes
--gargNetwork = undefined --gargNetwork = undefined
-- | Garg Node is Database Schema Typed as specification -- | Garg Node is Database Schema Typed as specification
-- gargNode gathers all the Nodes of all users on one Node -- gargNode gathers all the Nodes of all users on one Node
gargNode :: [Tree NodeType NodeType] gargNode :: [Tree NodeType]
gargNode = [userTree] gargNode = [userTree]
-- | User Tree simplified -- | User Tree simplified
userTree :: Tree NodeType NodeType userTree :: Tree NodeType
userTree = NodeT NodeUser [projectTree] userTree = NodeT NodeUser [projectTree]
-- | Project Tree -- | Project Tree
projectTree :: Tree NodeType NodeType projectTree :: Tree NodeType
projectTree = NodeT Project [corpusTree] projectTree = NodeT Project [corpusTree]
-- | Corpus Tree -- | Corpus Tree
corpusTree :: Tree NodeType NodeType corpusTree :: Tree NodeType
corpusTree = NodeT Corpus ( [ LeafT Document ] corpusTree = NodeT Corpus ( [ leafT Document ]
<> [ LeafT Lists ] <> [ leafT Lists ]
<> [ LeafT Metrics ] <> [ leafT Metrics ]
<> [ LeafT Classification] <> [ leafT Classification]
) )
-- TODO make instances of Nodes -- TODO make instances of Nodes
-- NP
-- * why NodeUser and not just User ?
-- * is this supposed to hold data ?
data NodeType = NodeUser | Project | Corpus | Document | DocumentCopy data NodeType = NodeUser | Project | Corpus | Document | DocumentCopy
| Classification | Classification
| Lists | Lists
...@@ -91,7 +100,7 @@ type NodeName = Text ...@@ -91,7 +100,7 @@ type NodeName = Text
-- | Then a Node can be either a Folder or a Corpus or a Document -- | Then a Node can be either a Folder or a Corpus or a Document
type NodeUser = Node HyperdataUser type NodeUser = Node HyperdataUser
type Folder = Node HyperdataFolder type Folder = Node HyperdataFolder
type Project = Folder type Project = Folder -- NP Node HyperdataProject ?
type Corpus = Node HyperdataCorpus type Corpus = Node HyperdataCorpus
type Document = Node HyperdataDocument type Document = Node HyperdataDocument
...@@ -105,14 +114,14 @@ type Favorites = Node HyperdataFavorites ...@@ -105,14 +114,14 @@ type Favorites = Node HyperdataFavorites
-- | Favorites Node enable Swap Node with some synonyms for clarity -- | Favorites Node enable Swap Node with some synonyms for clarity
type NodeSwap = Node HyperdataResource type NodeSwap = Node HyperdataResource
-- | Then a Node can be a List which as some synonyms -- | Then a Node can be a List which has some synonyms
type List = Node HyperdataList type List = Node HyperdataList
type StopList = List type StopList = List
type MainList = List type MainList = List
type MapList = List type MapList = List
type GroupList = List type GroupList = List
-- | Then a Node can be a Score which as some synonyms -- | Then a Node can be a Score which has some synonyms
type Score = Node HyperdataScore type Score = Node HyperdataScore
type Occurrences = Score type Occurrences = Score
type Cooccurrences = Score type Cooccurrences = Score
......
...@@ -10,6 +10,7 @@ import Data.Time (UTCTime) ...@@ -10,6 +10,7 @@ import Data.Time (UTCTime)
import Data.Gargantext.Utils.Prefix (unPrefix) import Data.Gargantext.Utils.Prefix (unPrefix)
import Data.Aeson.TH (deriveJSON) import Data.Aeson.TH (deriveJSON)
-- node_Id... ?
data NodePoly id typename userId parentId name date hyperdata = Node { node_id :: id data NodePoly id typename userId parentId name date hyperdata = Node { node_id :: id
, node_typename :: typename , node_typename :: typename
, node_userId :: userId , node_userId :: userId
...@@ -20,6 +21,7 @@ data NodePoly id typename userId parentId name date hyperdata = Node { node_id ...@@ -20,6 +21,7 @@ data NodePoly id typename userId parentId name date hyperdata = Node { node_id
, node_hyperdata :: hyperdata , node_hyperdata :: hyperdata
-- , node_titleAbstract :: titleAbstract -- , node_titleAbstract :: titleAbstract
} deriving (Show) } deriving (Show)
$(deriveJSON (unPrefix "node_") ''NodePoly)
data Status = Status { status_Date :: Maybe UTCTime data Status = Status { status_Date :: Maybe UTCTime
...@@ -77,6 +79,7 @@ data HyperdataUser = HyperdataUser { hyperdataUser_language :: Maybe Text ...@@ -77,6 +79,7 @@ data HyperdataUser = HyperdataUser { hyperdataUser_language :: Maybe Text
} deriving (Show, Generic) } deriving (Show, Generic)
$(deriveJSON (unPrefix "hyperdataUser_") ''HyperdataUser) $(deriveJSON (unPrefix "hyperdataUser_") ''HyperdataUser)
-- Preferences ?
data HyperdataFolder = HyperdataFolder { hyperdataFolder_Preferences :: Maybe Text data HyperdataFolder = HyperdataFolder { hyperdataFolder_Preferences :: Maybe Text
} deriving (Show, Generic) } deriving (Show, Generic)
......
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