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

[FIX] address for invitation is now in gargantext.ini

parent 21aed8c5
[gargantext] [gargantext]
# API url for server # Main url serving the FrontEnd
URL = http://localhost:8008/api/v1.0 URL = http://localhost
# Main API url serving the BackEnd
URL_BACKEND_API = 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
......
...@@ -71,7 +71,7 @@ import qualified Paths_gargantext as PG -- cabal magic build module ...@@ -71,7 +71,7 @@ import qualified Paths_gargantext as PG -- cabal magic build module
import qualified Gargantext.API.Public as Public import qualified Gargantext.API.Public as Public
import Gargantext.Prelude.Config (gc_url) import Gargantext.Prelude.Config (gc_url_backend_api)
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 (newEnv) import Gargantext.API.Admin.Settings (newEnv)
...@@ -92,7 +92,7 @@ startGargantext mode port file = do ...@@ -92,7 +92,7 @@ startGargantext mode port file = do
env <- newEnv port file env <- newEnv port file
portRouteInfo port portRouteInfo port
let baseUrl = env ^. env_gargConfig . gc_url let baseUrl = env ^. env_gargConfig . gc_url_backend_api
app <- makeApp env baseUrl app <- makeApp env baseUrl
mid <- makeDevMiddleware mode mid <- makeDevMiddleware mode
......
...@@ -14,39 +14,40 @@ Portability : POSIX ...@@ -14,39 +14,40 @@ Portability : POSIX
module Gargantext.Database.Action.User module Gargantext.Database.Action.User
where where
-- import Data.Maybe (catMaybes) import Control.Lens (view)
import Control.Monad.Random
import Data.Text (Text, unlines, splitOn) import Data.Text (Text, unlines, splitOn)
import Gargantext.Database.Query.Table.User
import Gargantext.Core.Types.Individu import Gargantext.Core.Types.Individu
import Gargantext.Prelude.Config
import Gargantext.Database.Action.Flow (getOrMkRoot)
import Gargantext.Database.Prelude import Gargantext.Database.Prelude
import Control.Monad.Random
import Gargantext.Prelude
import Gargantext.Prelude.Mail (gargMail, GargMail(..))
import Gargantext.Database.Query.Table.Node.Error (HasNodeError(..), nodeError, NodeError(..)) import Gargantext.Database.Query.Table.Node.Error (HasNodeError(..), nodeError, NodeError(..))
import Gargantext.Database.Action.Flow (getOrMkRoot) import Gargantext.Database.Query.Table.User
import Gargantext.Prelude
import Gargantext.Prelude.Crypto.Pass.User (gargPass) import Gargantext.Prelude.Crypto.Pass.User (gargPass)
import Gargantext.Prelude.Mail (gargMail, GargMail(..))
type EmailAddress = Text type EmailAddress = Text
------------------------------------------------------------------------ ------------------------------------------------------------------------
newUsers :: (CmdM env err m, MonadRandom m, HasNodeError err) => Text -> [Text] -> m Int64 newUsers :: (CmdM env err m, MonadRandom m, HasNodeError err)
newUsers address us = do => [EmailAddress] -> m Int64
newUsers us = do
us' <- mapM newUserQuick us us' <- mapM newUserQuick us
newUsers' address us' conf <- view hasConfig
newUsers' (_gc_url conf) us'
------------------------------------------------------------------------ ------------------------------------------------------------------------
newUserQuick :: (MonadRandom m) => Text -> m (NewUser GargPassword) newUserQuick :: (MonadRandom m)
=> Text -> m (NewUser GargPassword)
newUserQuick n = do newUserQuick n = do
pass <- gargPass pass <- gargPass
let (u,_m) = guessUserName n let (u,_m) = guessUserName n
pure (NewUser u n (GargPassword pass)) pure (NewUser u n (GargPassword pass))
-- | TODO better check for invalid email adress
guessUserName :: Text -> (Text,Text) guessUserName :: Text -> (Text,Text)
guessUserName n = case splitOn "@" n of guessUserName n = case splitOn "@" n of
[u',m'] -> if m' /= "" then (u',m') [u',m'] -> if m' /= "" then (u',m')
else panic "Email Invalid" else panic "Email Invalid"
_ -> panic "Email invalid" _ -> panic "Email invalid"
------------------------------------------------------------------------ ------------------------------------------------------------------------
newUser' :: HasNodeError err newUser' :: HasNodeError err
=> Text -> NewUser GargPassword -> Cmd err Int64 => Text -> NewUser GargPassword -> Cmd err Int64
......
...@@ -24,6 +24,7 @@ import Control.Lens (makeLenses) ...@@ -24,6 +24,7 @@ import Control.Lens (makeLenses)
data GargConfig = GargConfig { _gc_url :: !Text data GargConfig = GargConfig { _gc_url :: !Text
, _gc_url_backend_api :: !Text
, _gc_masteruser :: !Text , _gc_masteruser :: !Text
, _gc_secretkey :: !Text , _gc_secretkey :: !Text
...@@ -55,6 +56,7 @@ readConfig fp = do ...@@ -55,6 +56,7 @@ readConfig fp = do
Right p' -> p' Right p' -> p'
pure $ GargConfig (val "URL") pure $ GargConfig (val "URL")
(val "URL_BACKEND_API")
(val "MASTER_USER") (val "MASTER_USER")
(val "SECRET_KEY") (val "SECRET_KEY")
(cs $ val "DATA_FILEPATH") (cs $ val "DATA_FILEPATH")
...@@ -66,7 +68,8 @@ readConfig fp = do ...@@ -66,7 +68,8 @@ readConfig fp = do
(read $ cs $ val "MAX_DOCS_SCRAPERS") (read $ cs $ val "MAX_DOCS_SCRAPERS")
defaultConfig :: GargConfig defaultConfig :: GargConfig
defaultConfig = GargConfig "https://gargantext.org" defaultConfig = GargConfig "https://localhost"
"https://localhost:8008/api/v1.0"
"gargantua" "gargantua"
"secret" "secret"
"data" "data"
......
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