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

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

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