Commit 28a3fd84 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[MULTIUSER DEMO] insertion and config/hack.

parent b3d13d65
Pipeline #215 canceled with stage
......@@ -40,13 +40,11 @@ import Gargantext.Database.Utils (Cmd)
import Gargantext.Prelude hiding (reverse)
import Test.QuickCheck (elements, oneof)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import Gargantext.Core.Types.Individu (Username, Password, arbitraryUsername, arbitraryPassword)
---------------------------------------------------
-- | Main types for AUTH API
type Username = Text
type Password = Text
data AuthRequest = AuthRequest { _authReq_username :: Username
, _authReq_password :: Password
}
......@@ -76,18 +74,12 @@ type TreeId = NodeId
data CheckAuth = InvalidUser | InvalidPassword | Valid Token TreeId
deriving (Eq)
arbitraryUsername :: [Username]
arbitraryUsername = ["gargantua", "user1", "user2"]
arbitraryPassword :: [Password]
arbitraryPassword = map reverse arbitraryUsername
checkAuthRequest :: Username -> Password -> Cmd err CheckAuth
checkAuthRequest u p
| not (u `elem` arbitraryUsername) = pure InvalidUser
| u /= reverse p = pure InvalidPassword
| otherwise = do
muId <- getRoot u
muId <- getRoot "user1"
pure $ maybe InvalidUser (Valid "token" . _node_id) $ head muId
auth :: AuthRequest -> Cmd err AuthResponse
......
......@@ -11,13 +11,31 @@ Individu defintions
-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
module Gargantext.Core.Types.Individu
where
import Data.Text (Text)
import Gargantext.Prelude hiding (reverse)
import Data.Text (Text, pack, reverse)
type Username = Text
type Password = Text
type UsernameMaster = Username
type UsernameSimple = Username
arbitraryUsername :: [Username]
arbitraryUsername = ["gargantua"] <> users
where
users = zipWith (\a b -> a <> (pack . show) b)
(repeat "user") ([1..20]::[Int])
arbitraryPassword :: [Password]
arbitraryPassword = map reverse arbitraryUsername
......@@ -219,7 +219,7 @@ extractNgramsT doc = do
let institutes = map text2ngrams $ maybe ["Nothing"] (map toSchoolName . (splitOn ", ")) $ _hyperdataDocument_institutes doc
let authors = map text2ngrams $ maybe ["Nothing"] (splitOn ", ") $ _hyperdataDocument_authors doc
let leText = catMaybes [_hyperdataDocument_title doc, _hyperdataDocument_abstract doc]
terms' <- map text2ngrams <$> map (intercalate " " . _terms_label) <$> concat <$> liftIO (extractTerms (Mono EN) leText)
terms' <- map text2ngrams <$> map (intercalate " " . _terms_label) <$> concat <$> liftIO (extractTerms (Multi EN) leText)
pure $ DM.fromList $ [(source, DM.singleton Sources 1)]
<> [(i', DM.singleton Institutes 1) | i' <- institutes ]
......
......@@ -33,11 +33,13 @@ import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
import Data.Text (Text)
import Data.Time (UTCTime)
import GHC.Show(Show(..))
import Gargantext.Core.Types.Individu (Username)
import Gargantext.Core.Types.Individu (Username, arbitraryUsername)
import Gargantext.Database.Utils
import Gargantext.Prelude
import Opaleye
------------------------------------------------------------------------
------------------------------------------------------------------------
type UserId = Int
......@@ -106,29 +108,17 @@ userTable = Table "auth_user" (pUser User { user_id = optional "id"
insertUsers :: [UserWrite] -> Cmd err Int64
insertUsers us = mkCmd $ \c -> runInsertMany c userTable us
gargantuaUser :: UserWrite
gargantuaUser = User (Nothing) (pgStrictText "password")
(Nothing) (pgBool True) (pgStrictText "gargantua")
(pgStrictText "first_name")
(pgStrictText "last_name")
(pgStrictText "e@mail")
(pgBool True) (pgBool True) (Nothing)
simpleUser1 :: UserWrite
simpleUser1 = User (Nothing) (pgStrictText "password")
(Nothing) (pgBool False) (pgStrictText "user1")
gargantextUser :: Username -> UserWrite
gargantextUser u = User (Nothing) (pgStrictText "password")
(Nothing) (pgBool True) (pgStrictText u)
(pgStrictText "first_name")
(pgStrictText "last_name")
(pgStrictText "e@mail")
(pgBool False) (pgBool True) (Nothing)
(pgBool True) (pgBool True) (Nothing)
simpleUser2 :: UserWrite
simpleUser2 = User (Nothing) (pgStrictText "password")
(Nothing) (pgBool False) (pgStrictText "user2")
(pgStrictText "first_name")
(pgStrictText "last_name")
(pgStrictText "e@mail")
(pgBool False) (pgBool True) (Nothing)
insertUsersDemo :: Cmd err Int64
insertUsersDemo = insertUsers $ map (\u -> gargantextUser u) arbitraryUsername
------------------------------------------------------------------
......
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