Commit 6999a68e authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT] Public screenshot to public home

parent d0101d87
[gargantext] [gargantext]
# API url for server
URL = http://localhost:8008/api/v1.0
# Needed to instantiate the first users and first data # Needed to instantiate the first users and first data
MASTER_USER = gargantua MASTER_USER = gargantua
......
...@@ -54,6 +54,7 @@ import Data.Version (showVersion) ...@@ -54,6 +54,7 @@ import Data.Version (showVersion)
import GHC.Base (Applicative) import GHC.Base (Applicative)
import GHC.Generics (D1, Meta (..), Rep, Generic) import GHC.Generics (D1, Meta (..), Rep, Generic)
import GHC.TypeLits (AppendSymbol, Symbol) import GHC.TypeLits (AppendSymbol, Symbol)
import Gargantext.Prelude.Config (gc_url)
import Gargantext.API.Admin.Auth (AuthContext, auth) import Gargantext.API.Admin.Auth (AuthContext, auth)
import Gargantext.API.Admin.FrontEnd (frontEndServer) import Gargantext.API.Admin.FrontEnd (frontEndServer)
import Gargantext.API.Admin.Settings import Gargantext.API.Admin.Settings
...@@ -86,7 +87,10 @@ startGargantext :: Mode -> PortNumber -> FilePath -> IO () ...@@ -86,7 +87,10 @@ startGargantext :: Mode -> PortNumber -> FilePath -> IO ()
startGargantext mode port file = do startGargantext mode port file = do
env <- newEnv port file env <- newEnv port file
portRouteInfo port portRouteInfo port
app <- makeApp env
let baseUrl = env ^. env_gargConfig . gc_url
app <- makeApp env baseUrl
mid <- makeDevMiddleware mode mid <- makeDevMiddleware mode
run port (mid app) `finally` stopGargantext env run port (mid app) `finally` stopGargantext env
...@@ -214,36 +218,37 @@ makeDevMiddleware mode = do ...@@ -214,36 +218,37 @@ makeDevMiddleware mode = do
-- | API Global -- | API Global
--------------------------------------------------------------------- ---------------------------------------------------------------------
-- | Server declarations -- | Server declarations
server :: forall env. EnvC env => env -> IO (Server API) server :: forall env. EnvC env => env -> Text -> IO (Server API)
server env = do server env baseUrl = do
-- orchestrator <- scrapyOrchestrator env -- orchestrator <- scrapyOrchestrator env
pure $ schemaUiServer swaggerDoc pure $ schemaUiServer swaggerDoc
:<|> hoistServerWithContext :<|> hoistServerWithContext
(Proxy :: Proxy GargAPI) (Proxy :: Proxy GargAPI)
(Proxy :: Proxy AuthContext) (Proxy :: Proxy AuthContext)
transform transform
serverGargAPI (serverGargAPI baseUrl)
:<|> frontEndServer :<|> frontEndServer
where where
transform :: forall a. GargServerM env GargError a -> Handler a transform :: forall a. GargServerM env GargError a -> Handler a
transform = Handler . withExceptT showAsServantErr . (`runReaderT` env) transform = Handler . withExceptT showAsServantErr . (`runReaderT` env)
showAsServantErr :: GargError -> ServerError showAsServantErr :: GargError -> ServerError
showAsServantErr (GargServerError err) = err showAsServantErr (GargServerError err) = err
showAsServantErr a = err500 { errBody = BL8.pack $ show a } showAsServantErr a = err500 { errBody = BL8.pack $ show a }
--------------------------- ---------------------------
serverGargAPI :: GargServerT env err (GargServerM env err) GargAPI serverGargAPI :: Text -> GargServerT env err (GargServerM env err) GargAPI
serverGargAPI -- orchestrator serverGargAPI baseUrl -- orchestrator
= auth = auth
:<|> gargVersion :<|> gargVersion
:<|> serverPrivateGargAPI :<|> serverPrivateGargAPI
:<|> Public.api :<|> (Public.api baseUrl)
-- :<|> orchestrator -- :<|> orchestrator
where where
gargVersion :: GargServer GargVersion gargVersion :: GargServer GargVersion
gargVersion = pure (cs $ showVersion PG.version) gargVersion = pure (cs $ showVersion PG.version)
...@@ -265,8 +270,8 @@ serverGargAdminAPI = roots ...@@ -265,8 +270,8 @@ serverGargAdminAPI = roots
--gargMock :: Server GargAPI --gargMock :: Server GargAPI
--gargMock = mock apiGarg Proxy --gargMock = mock apiGarg Proxy
--------------------------------------------------------------------- ---------------------------------------------------------------------
makeApp :: EnvC env => env -> IO Application makeApp :: EnvC env => env -> Text -> IO Application
makeApp env = serveWithContext api cfg <$> server env makeApp env baseUrl = serveWithContext api cfg <$> server env baseUrl
where where
cfg :: Servant.Context AuthContext cfg :: Servant.Context AuthContext
cfg = env ^. settings . jwtSettings cfg = env ^. settings . jwtSettings
......
...@@ -41,8 +41,11 @@ type API = Summary " Public API" ...@@ -41,8 +41,11 @@ type API = Summary " Public API"
:> Get '[JSON] [PublicData] :> Get '[JSON] [PublicData]
api :: HasNodeError err api :: HasNodeError err
=> Cmd err [PublicData] => Text -> Cmd err [PublicData]
api = catMaybes <$> map toPublicData <$> filterPublicDatas <$> selectPublic api base = catMaybes
<$> map (toPublicData base)
<$> filterPublicDatas
<$> selectPublic
selectPublic :: HasNodeError err selectPublic :: HasNodeError err
...@@ -52,20 +55,24 @@ selectPublic = selectPublicNodes ...@@ -52,20 +55,24 @@ selectPublic = selectPublicNodes
-- For tests only -- For tests only
-- pure $ replicate 6 defaultPublicData -- pure $ replicate 6 defaultPublicData
filterPublicDatas :: [( Node HyperdataFolder, Maybe Int)] -> [(Node HyperdataFolder, [NodeId])] filterPublicDatas :: [(Node HyperdataFolder, Maybe Int)]
filterPublicDatas datas = map (\(n,mi) -> let mi' = NodeId <$> mi in -> [(Node HyperdataFolder, [NodeId])]
( _node_id n, (n, maybe [] (:[]) mi' )) filterPublicDatas datas =
) datas map (\(n,mi) ->
& Map.fromListWith (\(n1,i1) (_n2,i2) -> (n1, i1 <> i2)) let mi' = NodeId <$> mi in
& Map.filter (not . null . snd) ( _node_id n, (n, maybe [] (:[]) mi' ))
& Map.elems ) datas
& Map.fromListWith (\(n1,i1) (_n2,i2) -> (n1, i1 <> i2))
& Map.filter (not . null . snd)
toPublicData :: (Node HyperdataFolder, [NodeId]) -> Maybe PublicData & Map.elems
toPublicData (n , _mn) = PublicData <$> (hd ^? (_Just . hf_data . cf_title))
<*> (hd ^? (_Just . hf_data . cf_desc)) -- http://localhost:8008/api/v1.0/node/23543/file/download<Paste>
<*> Just "images/Gargantextuel-212x300.jpg" -- http://localhost:8000/images/Gargantextuel-212x300.jpg
<*> Just "https://.." toPublicData :: Text -> (Node HyperdataFolder, [NodeId]) -> Maybe PublicData
toPublicData base (n , mn) = PublicData <$> (hd ^? (_Just . hf_data . cf_title))
<*> (hd ^? (_Just . hf_data . cf_desc ))
<*> (Just $ url' mn) -- "images/Gargantextuel-212x300.jpg"
<*> (Just $ url' mn)
<*> Just (cs $ show $ utc2year (n^.node_date)) <*> Just (cs $ show $ utc2year (n^.node_date))
<*> (hd ^? (_Just . hf_data . cf_query)) <*> (hd ^? (_Just . hf_data . cf_query))
<*> (hd ^? (_Just . hf_data . cf_authors)) <*> (hd ^? (_Just . hf_data . cf_authors))
...@@ -73,6 +80,11 @@ toPublicData (n , _mn) = PublicData <$> (hd ^? (_Just . hf_data . cf_title)) ...@@ -73,6 +80,11 @@ toPublicData (n , _mn) = PublicData <$> (hd ^? (_Just . hf_data . cf_title))
hd = head hd = head
$ filter (\(HyperdataField cd _ _) -> cd == JSON) $ filter (\(HyperdataField cd _ _) -> cd == JSON)
$ n^. (node_hyperdata . hc_fields) $ n^. (node_hyperdata . hc_fields)
url' :: [NodeId] -> Text
url' mn' = base
<> "/node/"
<> (cs $ show $ (maybe 0 unNodeId $ head mn'))
<> "/file/download"
data PublicData = PublicData data PublicData = PublicData
......
...@@ -29,7 +29,7 @@ import Gargantext.Prelude ...@@ -29,7 +29,7 @@ import Gargantext.Prelude
-- | TODO move in Config of Gargantext -- | TODO move in Config of Gargantext
publicNodeTypes :: [NodeType] publicNodeTypes :: [NodeType]
publicNodeTypes = [NodeDashboard, NodeGraph, NodePhylo] publicNodeTypes = [NodeDashboard, NodeGraph, NodePhylo, NodeFile]
------------------------------------------------------------------------ ------------------------------------------------------------------------
......
...@@ -124,6 +124,9 @@ pgNodeId = O.pgInt4 . id2int ...@@ -124,6 +124,9 @@ pgNodeId = O.pgInt4 . id2int
newtype NodeId = NodeId Int newtype NodeId = NodeId Int
deriving (Show, Read, Generic, Num, Eq, Ord, Enum, ToJSONKey, FromJSONKey, ToJSON, FromJSON) deriving (Show, Read, Generic, Num, Eq, Ord, Enum, ToJSONKey, FromJSONKey, ToJSON, FromJSON)
unNodeId :: NodeId -> Int
unNodeId (NodeId n) = n
instance Serialise NodeId instance Serialise NodeId
instance ToField NodeId where instance ToField NodeId where
......
...@@ -23,7 +23,9 @@ import GHC.Generics (Generic) ...@@ -23,7 +23,9 @@ import GHC.Generics (Generic)
import Control.Lens (makeLenses) import Control.Lens (makeLenses)
data GargConfig = GargConfig { _gc_masteruser :: !Text data GargConfig = GargConfig { _gc_url :: !Text
, _gc_masteruser :: !Text
, _gc_secretkey :: !Text , _gc_secretkey :: !Text
, _gc_datafilepath :: !FilePath , _gc_datafilepath :: !FilePath
...@@ -52,7 +54,8 @@ readConfig fp = do ...@@ -52,7 +54,8 @@ readConfig fp = do
Left _ -> panic (pack $ "ERROR: add " <> x <> " to your gargantext.ini") Left _ -> panic (pack $ "ERROR: add " <> x <> " to your gargantext.ini")
Right p' -> p' Right p' -> p'
pure $ GargConfig (val "MASTER_USER") pure $ GargConfig (val "URL")
(val "MASTER_USER")
(val "SECRET_KEY") (val "SECRET_KEY")
(cs $ val "DATA_FILEPATH") (cs $ val "DATA_FILEPATH")
(cs $ val "REPO_FILEPATH") (cs $ val "REPO_FILEPATH")
...@@ -63,7 +66,8 @@ readConfig fp = do ...@@ -63,7 +66,8 @@ readConfig fp = do
(read $ cs $ val "MAX_DOCS_SCRAPERS") (read $ cs $ val "MAX_DOCS_SCRAPERS")
defaultConfig :: GargConfig defaultConfig :: GargConfig
defaultConfig = GargConfig "gargantua" defaultConfig = GargConfig "https://gargantext.org"
"gargantua"
"secret" "secret"
"data" "data"
"repos/" "repos/"
......
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