Commit 6d114f74 authored by Alexandre Delanoë's avatar Alexandre Delanoë

Merge branch 'dev' into dev-forest

parents 7b004cb5 f1722b30
module Gargantext.Config.REST where module Gargantext.Config.REST where
import Gargantext.Prelude import Prelude (Unit, bind, pure, ($), (<$>), (<<<), (<>))
import Gargantext.Ends
import Affjax (defaultRequest, printResponseFormatError, request) import Affjax (defaultRequest, printResponseFormatError, request)
import Affjax.RequestBody (RequestBody(..), string) import Affjax.RequestBody (RequestBody(..), string)
import Affjax.RequestHeader (RequestHeader(..)) import Affjax.RequestHeader (RequestHeader(..))
import Affjax.ResponseFormat as ResponseFormat import Affjax.ResponseFormat as ResponseFormat
import Effect.Class (liftEffect)
import Data.Argonaut (class DecodeJson, decodeJson, class EncodeJson, encodeJson) import Data.Argonaut (class DecodeJson, decodeJson, class EncodeJson, encodeJson)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.HTTP.Method (Method(..)) import Data.HTTP.Method (Method(..))
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.MediaType.Common (applicationFormURLEncoded, applicationJSON) import Data.MediaType.Common (applicationFormURLEncoded, applicationJSON)
import Data.Foldable (foldMap) import Data.Foldable (foldMap)
import DOM.Simple.Console (log)
import Effect.Aff (Aff, throwError) import Effect.Aff (Aff, throwError)
import Effect.Exception (error) import Effect.Exception (error)
...@@ -36,12 +37,12 @@ send m mtoken url reqbody = do ...@@ -36,12 +37,12 @@ send m mtoken url reqbody = do
} }
case affResp.body of case affResp.body of
Left err -> do Left err -> do
_ <- logs $ printResponseFormatError err _ <- liftEffect $ log $ printResponseFormatError err
throwError $ error $ printResponseFormatError err throwError $ error $ printResponseFormatError err
Right json -> do Right json -> do
--_ <- logs $ show json.status --_ <- liftEffect $ log json.status
--_ <- logs $ show json.headers --_ <- liftEffect $ log json.headers
--_ <- logs $ show json.body --_ <- liftEffect $ log json.body
case decodeJson json of case decodeJson json of
Left err -> throwError $ error $ "decodeJson affResp.body: " <> err Left err -> throwError $ error $ "decodeJson affResp.body: " <> err
Right b -> pure b Right b -> pure b
...@@ -83,12 +84,12 @@ postWwwUrlencoded mtoken url body = do ...@@ -83,12 +84,12 @@ postWwwUrlencoded mtoken url body = do
} }
case affResp.body of case affResp.body of
Left err -> do Left err -> do
_ <- logs $ printResponseFormatError err _ <- liftEffect $ log $ printResponseFormatError err
throwError $ error $ printResponseFormatError err throwError $ error $ printResponseFormatError err
Right json -> do Right json -> do
--_ <- logs $ show json.status --_ <- liftEffect $ log json.status
--_ <- logs $ show json.headers --_ <- liftEffect $ log json.headers
--_ <- logs $ show json.body --_ <- liftEffect $ log json.body
case decodeJson json of case decodeJson json of
Left err -> throwError $ error $ "decodeJson affResp.body: " <> err Left err -> throwError $ error $ "decodeJson affResp.body: " <> err
Right b -> pure b Right b -> pure b
...@@ -4,7 +4,7 @@ module Gargantext.Ends ...@@ -4,7 +4,7 @@ module Gargantext.Ends
where where
import Prelude (class Eq, class Show, identity, show, ($), (<>), bind, pure, (<<<), (==)) import Prelude (class Eq, class Show, identity, show, ($), (<>), bind, pure, (<<<), (==))
import Data.Argonaut ( class DecodeJson, decodeJson, class EncodeJson, encodeJson, (:=), (~>), jsonEmptyObject, (.:)) import Data.Argonaut ( class DecodeJson, decodeJson, class EncodeJson, (:=), (~>), jsonEmptyObject, (.:))
import Data.Foldable (foldMap) import Data.Foldable (foldMap)
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Eq (genericEq) import Data.Generic.Rep.Eq (genericEq)
......
-- | A module for authenticating to create sessions and handling them -- | A module for authenticating to create sessions and handling them
module Gargantext.Sessions where module Gargantext.Sessions where
import Prelude (class Eq, class Show, Unit, const, otherwise, pure, show, unit, ($), (*>), (<*), (<$>), (<>), (==), (/=), (>>=), (>=>), (<<<), bind, map) import Prelude (class Eq, class Show, Unit, const, otherwise, pure, show, unit, ($), (*>), (<*), (<$>), (<>), (==), (/=), (>>=), (<<<), bind)
import Control.Monad.Except (runExcept) import Data.Argonaut ( class DecodeJson, decodeJson, class EncodeJson, encodeJson, (:=), (~>), (.:))
import Data.Argonaut ( class DecodeJson, decodeJson, class EncodeJson, encodeJson, (:=), (~>), (.:), Json)
import Data.Argonaut.Core (Json, fromArray, jsonEmptyObject, stringify) import Data.Argonaut.Core (Json, fromArray, jsonEmptyObject, stringify)
import Data.Argonaut.Parser (jsonParser) import Data.Argonaut.Parser (jsonParser)
import Data.Array as A import Data.Array as A
...@@ -26,7 +25,6 @@ import Gargantext.Components.Login.Types ...@@ -26,7 +25,6 @@ import Gargantext.Components.Login.Types
import Gargantext.Config.REST as REST import Gargantext.Config.REST as REST
import Gargantext.Ends (class ToUrl, Backend, backendUrl, toUrl, sessionPath) import Gargantext.Ends (class ToUrl, Backend, backendUrl, toUrl, sessionPath)
import Gargantext.Routes (SessionRoute) import Gargantext.Routes (SessionRoute)
import Gargantext.Prelude (logs)
import Gargantext.Types (NodePath, SessionId(..), nodePath) import Gargantext.Types (NodePath, SessionId(..), nodePath)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
...@@ -100,7 +98,7 @@ instance decodeJsonSessions :: DecodeJson Sessions where ...@@ -100,7 +98,7 @@ instance decodeJsonSessions :: DecodeJson Sessions where
where where
decodeSessions :: Json -> Either String (Array Session) decodeSessions :: Json -> Either String (Array Session)
decodeSessions json = decodeJson json decodeSessions json2 = decodeJson json2
>>= \obj -> obj .: "sessions" >>= \obj -> obj .: "sessions"
>>= traverse decodeJson >>= traverse decodeJson
...@@ -192,10 +190,10 @@ mapLeft _ (Right r) = Right r ...@@ -192,10 +190,10 @@ mapLeft _ (Right r) = Right r
saveSessions :: Sessions -> Effect Sessions saveSessions :: Sessions -> Effect Sessions
saveSessions sessions = effect *> pure sessions where saveSessions sessions = effect *> pure sessions where
remove = getls >>= removeItem localStorageKey rem = getls >>= removeItem localStorageKey
set v = getls >>= setItem localStorageKey v set v = getls >>= setItem localStorageKey v
effect effect
| null sessions = remove | null sessions = rem
| otherwise = set (stringify $ encodeJson sessions) | otherwise = set (stringify $ encodeJson sessions)
postAuthRequest :: Backend -> AuthRequest -> Aff (Either String Session) postAuthRequest :: Backend -> AuthRequest -> Aff (Either String Session)
......
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