Commit 37e654f2 authored by Sudhir Kumar's avatar Sudhir Kumar

reverted unsafeCoerce

parent 9c650bf5
...@@ -3,6 +3,7 @@ module Gargantext.Components.GraphExplorer.Sigmajs where ...@@ -3,6 +3,7 @@ module Gargantext.Components.GraphExplorer.Sigmajs where
import Prelude import Prelude
import Effect (Effect) import Effect (Effect)
import Prim.Row (class Union)
import React (ReactClass, ReactElement, createElement) import React (ReactClass, ReactElement, createElement)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
......
...@@ -2,18 +2,27 @@ module Gargantext.Components.Login where ...@@ -2,18 +2,27 @@ module Gargantext.Components.Login where
import Prelude hiding (div) import Prelude hiding (div)
import Effect (Effect) import Affjax (defaultRequest, request)
import Affjax.RequestHeader (RequestHeader(..))
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, jsonEmptyObject, (.?), (:=), (~>)) import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, jsonEmptyObject, (.?), (:=), (~>))
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.HTTP.Method (Method(..)) import Data.HTTP.Method (Method(..))
import Data.Lens (over) import Data.Lens (over)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.MediaType.Common (applicationJSON) import Data.MediaType.Common (applicationJSON)
import Effect (Effect)
import Effect.Aff (Aff, attempt)
import Effect.Aff.Class (liftAff)
import Effect.Class (liftEffect)
import Effect.Console (log)
import Gargantext.Components.Modals.Modal (modalHide) import Gargantext.Components.Modals.Modal (modalHide)
import React.DOM (a, button, div, h2, h4, h5, i, input, label, p, span, text) import React.DOM (a, button, div, h2, h4, h5, i, input, label, p, span, text)
import React.DOM.Props (_data, _id, _type, aria, className, href, maxLength, name, onClick, onInput, placeholder, role, target, value) import React.DOM.Props (_data, _id, _type, aria, className, href, maxLength, name, onClick, onInput, placeholder, role, target, value)
import Thermite (PerformAction, Render, Spec, _render, modifyState, simpleSpec) import Thermite (PerformAction, Render, Spec, _render, modifyState, simpleSpec)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
import Web.HTML (window)
import Web.HTML.Window (localStorage)
import Web.Storage.Storage (getItem, setItem)
-- TODO: ask for login (modal) or account creation after 15 mn when user is not logged and has made one search at least -- TODO: ask for login (modal) or account creation after 15 mn when user is not logged and has made one search at least
...@@ -44,7 +53,7 @@ data Action ...@@ -44,7 +53,7 @@ data Action
performAction :: forall props. PerformAction State props Action performAction :: forall props. PerformAction State props Action
performAction NoOp _ _ = void do performAction NoOp _ _ = void do
modifyState id modifyState identity
performAction (SetUserName usr) _ _ = void do performAction (SetUserName usr) _ _ = void do
modifyState \(State state) -> State $ state { username = usr } modifyState \(State state) -> State $ state { username = usr }
...@@ -57,7 +66,7 @@ performAction (SetPassword pwd) _ _ = void do ...@@ -57,7 +66,7 @@ performAction (SetPassword pwd) _ _ = void do
performAction Login _ (State state) = void do performAction Login _ (State state) = void do
--lift $ setHash "/search" --lift $ setHash "/search"
liftEff $ modalHide "loginModal" liftEffect $ modalHide "loginModal"
modifyState \(State state) -> State $ state {loginC = true} modifyState \(State state) -> State $ state {loginC = true}
-- res <- lift $ loginReq $ LoginReq { username : state.username, password : state.password } -- res <- lift $ loginReq $ LoginReq { username : state.username, password : state.password }
-- case res of -- case res of
...@@ -133,13 +142,13 @@ renderSpec = simpleSpec performAction render ...@@ -133,13 +142,13 @@ renderSpec = simpleSpec performAction render
[ input [_type "hidden", [ input [_type "hidden",
name "csrfmiddlewaretoken", name "csrfmiddlewaretoken",
value "Wy52D2nor8kC1r1Y4GrsrSIxQ2eqW8UwkdiQQshMoRwobzU4uldknRUhP0j4WcEM" ] value "Wy52D2nor8kC1r1Y4GrsrSIxQ2eqW8UwkdiQQshMoRwobzU4uldknRUhP0j4WcEM" ]
[]
, div [className "form-group"] , div [className "form-group"]
[ p [] [text state.errorMessage] [ p [] [text state.errorMessage]
, input [className "form-control", _id "id_username",maxLength "254", name "username", placeholder "username", _type "text",value state.username, onInput \e -> dispatch (SetUserName (unsafeEventValue e))] [] , input [className "form-control", _id "id_username",maxLength "254", name "username", placeholder "username", _type "text",value state.username, onInput \e -> dispatch (SetUserName (unsafeEventValue e))]
] ]
, div [className "form-group"] , div [className "form-group"]
[ input [className "form-control", _id "id_password", name "password", placeholder "password", _type "password",value state.password,onInput \e -> dispatch (SetPassword (unsafeEventValue e))] [] [ input [className "form-control", _id "id_password", name "password", placeholder "password", _type "password",value state.password,onInput \e -> dispatch (SetPassword (unsafeEventValue e))]
, div [className "clearfix"] [] , div [className "clearfix"] []
] ]
, div [className "center"] , div [className "center"]
...@@ -147,8 +156,6 @@ renderSpec = simpleSpec performAction render ...@@ -147,8 +156,6 @@ renderSpec = simpleSpec performAction render
label [] [ label [] [
div [className "checkbox"] div [className "checkbox"]
[ input [_id "terms-accept", _type "checkbox", value "", className "checkbox"] [ input [_id "terms-accept", _type "checkbox", value "", className "checkbox"]
[
]
, text "I accept the terms of uses ", , text "I accept the terms of uses ",
a [href "http://gitlab.iscpif.fr/humanities/tofu/tree/master"] [text "[Read the terms of use]"] a [href "http://gitlab.iscpif.fr/humanities/tofu/tree/master"] [text "[Read the terms of use]"]
] ]
...@@ -243,7 +250,7 @@ loginReq encodeData = ...@@ -243,7 +250,7 @@ loginReq encodeData =
} }
in in
do do
affResp <- liftAff $ attempt $ affjax setting affResp <- liftAff $ attempt $ request setting
case affResp of case affResp of
Left err -> do Left err -> do
liftAff $ log $ show err liftAff $ log $ show err
...@@ -257,7 +264,7 @@ loginReq encodeData = ...@@ -257,7 +264,7 @@ loginReq encodeData =
Left e -> Left e ->
liftAff $ log $ "Error Decoding : " <> show e liftAff $ log $ "Error Decoding : " <> show e
Right (LoginRes res1) -> Right (LoginRes res1) ->
liftEff $ setToken res1.token liftEffect $ setToken res1.token
pure res pure res
instance decodeLoginRes :: DecodeJson LoginRes where instance decodeLoginRes :: DecodeJson LoginRes where
......
...@@ -21,10 +21,12 @@ module Gargantext.Components.RandomText where ...@@ -21,10 +21,12 @@ module Gargantext.Components.RandomText where
import Prelude import Prelude
import Effect (Effect)
import Data.Array (drop, dropEnd, filter, foldl, head, length, tail, take, takeEnd, (!!)) import Data.Array (drop, dropEnd, filter, foldl, head, length, tail, take, takeEnd, (!!))
import Data.Maybe (Maybe(Nothing, Just), fromJust) import Data.Maybe (Maybe(Nothing, Just), fromJust)
import Data.String (Pattern(..), fromCharArray, split, toCharArray) import Data.String (Pattern(..), split)
import Data.String.CodeUnits (fromCharArray, toCharArray)
import Effect (Effect)
import Effect.Random (randomInt)
import Partial (crash) import Partial (crash)
import Partial.Unsafe (unsafePartial) import Partial.Unsafe (unsafePartial)
...@@ -60,7 +62,7 @@ data RandomWheel a = RandomWheel { before :: Array a ...@@ -60,7 +62,7 @@ data RandomWheel a = RandomWheel { before :: Array a
, after :: Array a , after :: Array a
} }
randomPart :: forall a b. Array b -> Effect (Array b) randomPart :: forall b. Array b -> Effect (Array b)
randomPart array = randomArrayPoly middle >>= \(middle') -> pure ( start <> middle' <> end) randomPart array = randomArrayPoly middle >>= \(middle') -> pure ( start <> middle' <> end)
where where
start = take 2 array start = take 2 array
...@@ -68,13 +70,13 @@ randomPart array = randomArrayPoly middle >>= \(middle') -> pure ( start <> midd ...@@ -68,13 +70,13 @@ randomPart array = randomArrayPoly middle >>= \(middle') -> pure ( start <> midd
end = takeEnd 2 array end = takeEnd 2 array
randomArrayPoly :: forall a b. Array a -> Effect (Array a) randomArrayPoly :: forall a. Array a -> Effect (Array a)
randomArrayPoly wheel = case head wheel of randomArrayPoly wheel = case head wheel of
Nothing -> pure [] Nothing -> pure []
Just wheel' -> randomWheel (RandomWheel { before:wheel, during:wheel', after:[]}) Just wheel' -> randomWheel (RandomWheel { before:wheel, during:wheel', after:[]})
>>= \(RandomWheel rand) -> (pure rand.after) >>= \(RandomWheel rand) -> (pure rand.after)
randomWheel :: forall a b. RandomWheel b -> Effect (RandomWheel b) randomWheel :: forall b. RandomWheel b -> Effect (RandomWheel b)
randomWheel (RandomWheel {before:[], during:d, after:a}) = randomWheel (RandomWheel {before:[], during:d, after:a}) =
pure (RandomWheel {before:[], during:d, after:a}) pure (RandomWheel {before:[], during:d, after:a})
...@@ -83,7 +85,7 @@ randomWheel (RandomWheel {before:b, during:d, after:a}) = do ...@@ -83,7 +85,7 @@ randomWheel (RandomWheel {before:b, during:d, after:a}) = do
randomWheel $ RandomWheel {before:b', during:d', after:(a <> [d'])} randomWheel $ RandomWheel {before:b', during:d', after:(a <> [d'])}
randomArray :: forall a b. Array b -> Effect (RandomWheel b) randomArray :: forall b. Array b -> Effect (RandomWheel b)
randomArray array = unsafePartial $ do randomArray array = unsafePartial $ do
n <- randomInt 0 (length array - 1) n <- randomInt 0 (length array - 1)
......
...@@ -2,10 +2,15 @@ module Gargantext.Components.Tree where ...@@ -2,10 +2,15 @@ module Gargantext.Components.Tree where
import Prelude hiding (div) import Prelude hiding (div)
import Affjax (defaultRequest, request)
import Data.Argonaut (class DecodeJson, decodeJson, (.?)) import Data.Argonaut (class DecodeJson, decodeJson, (.?))
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.HTTP.Method (Method(..)) import Data.HTTP.Method (Method(..))
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Effect.Aff (Aff, attempt)
import Effect.Aff.Class (liftAff)
import Effect.Class (liftEffect)
import Effect.Console (log)
import React (ReactElement) import React (ReactElement)
import React.DOM (a, div, i, li, text, ul) import React.DOM (a, div, i, li, text, ul)
import React.DOM.Props (Props, className, href, onClick) import React.DOM.Props (Props, className, href, onClick)
...@@ -27,8 +32,9 @@ type State = FTree ...@@ -27,8 +32,9 @@ type State = FTree
initialState :: State initialState :: State
initialState = NLeaf (Tuple "" "") initialState = NLeaf (Tuple "" "")
performAction :: PerformAction _ State _ Action performAction :: PerformAction State _ Action
performAction (ToggleFolder i) _ _ = void (cotransform (\td -> toggleNode i td)) performAction (ToggleFolder i) _ _ = void $
cotransform (\td -> toggleNode i td)
toggleNode :: forall t10. Int -> NTree t10 -> NTree t10 toggleNode :: forall t10. Int -> NTree t10 -> NTree t10
toggleNode sid (NNode iid open name ary) = toggleNode sid (NNode iid open name ary) =
...@@ -127,19 +133,19 @@ instance decodeJsonLNode :: DecodeJson LNode where ...@@ -127,19 +133,19 @@ instance decodeJsonLNode :: DecodeJson LNode where
loadDefaultNode :: Aff (Either String (Array LNode)) loadDefaultNode :: Aff (Either String (Array LNode))
loadDefaultNode = do loadDefaultNode = do
res <- liftAff $ attempt $ affjax defaultRequest res <- liftAff $ attempt $ request defaultRequest
{ url = "http://localhost:8008/user" { url = "http://localhost:8008/user"
, method = Left GET , method = Left GET
} }
case res of case res of
Left err -> do Left err -> do
_ <- liftEff $ log $ show err _ <- liftEffect $ log $ show err
pure $ Left $ show err pure $ Left $ show err
Right a -> do Right a -> do
_ <- liftEff $ log $ show a.status _ <- liftEffect $ log $ show a.status
_ <- liftEff $ log $ show a.headers _ <- liftEffect $ log $ show a.headers
_ <- liftEff $ log $ show a.response _ <- liftEffect $ log $ show a.body
let resp = decodeJson a.response let resp = decodeJson a.body
pure resp pure resp
......
...@@ -2,15 +2,19 @@ module Gargantext.Config.REST where ...@@ -2,15 +2,19 @@ module Gargantext.Config.REST where
import Prelude import Prelude
import Affjax (defaultRequest, request)
import Affjax.RequestHeader (RequestHeader(..))
import Data.Argonaut (class DecodeJson, decodeJson) import Data.Argonaut (class DecodeJson, decodeJson)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.HTTP.Method (Method(..)) import Data.HTTP.Method (Method(..))
import Data.MediaType.Common (applicationJSON) import Data.MediaType.Common (applicationJSON)
import Effect.Aff (Aff, attempt)
import Effect.Aff.Class (liftAff)
get :: forall t2 t31. DecodeJson t31 => String -> get :: forall t31. DecodeJson t31 => String ->
Aff (Either String t31) Aff (Either String t31)
get url = do get url = do
affResp <- liftAff $ attempt $ affjax defaultRequest affResp <- liftAff $ attempt $ request defaultRequest
{ method = Left GET { method = Left GET
, url = url , url = url
, headers = [ ContentType applicationJSON , headers = [ ContentType applicationJSON
...@@ -22,5 +26,5 @@ get url = do ...@@ -22,5 +26,5 @@ get url = do
Left err -> do Left err -> do
pure $ Left $ show err pure $ Left $ show err
Right a -> do Right a -> do
let res = decodeJson a.response let res = decodeJson a.body
pure res pure res
...@@ -3,8 +3,8 @@ module Gargantext.Pages.Corpus.Doc.Annotation where ...@@ -3,8 +3,8 @@ module Gargantext.Pages.Corpus.Doc.Annotation where
import Prelude hiding (div) import Prelude hiding (div)
import React (ReactElement) import React (ReactElement)
import React.DOM (a, button, div, h4, h6, input, li, nav, option, p, select, span, text, ul) import React.DOM (a, button, div, h4, h6, input, li, nav, option, p, select, span, text, ul)
import React.DOM.Props (_data, _id, _type, aria, className, href, name, onChange, onInput, placeholder, role, selected, style, value) import React.DOM.Props (_data, _id, _type, aria, className, href, name, onChange, onInput, placeholder, role, style, value)
import Thermite (PerformAction, Render, Spec, cotransform, modifyState, simpleSpec) import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
...@@ -27,7 +27,7 @@ data Action ...@@ -27,7 +27,7 @@ data Action
| SetInput String | SetInput String
performAction :: PerformAction State _ Action performAction :: forall props. PerformAction State props Action
performAction NoOp _ _ = pure unit performAction NoOp _ _ = pure unit
performAction (ChangeString ps) _ _ = pure unit performAction (ChangeString ps) _ _ = pure unit
...@@ -39,10 +39,10 @@ performAction (SetInput ps) _ _ = void do ...@@ -39,10 +39,10 @@ performAction (SetInput ps) _ _ = void do
docview :: Spec State _ Action docview :: forall props. Spec State props Action
docview = simpleSpec performAction render docview = simpleSpec performAction render
where where
render :: Render State _ Action render :: Render State props Action
render dispatch _ state _ = render dispatch _ state _ =
[ [
div [className "container1"] div [className "container1"]
...@@ -76,7 +76,7 @@ docview = simpleSpec performAction render ...@@ -76,7 +76,7 @@ docview = simpleSpec performAction render
[ [
h6 [] [text "Add a free term to STOPLIST"] h6 [] [text "Add a free term to STOPLIST"]
, div [className "form-group"] , div [className "form-group"]
[ input [className "form-control", _id "id_password", name "password", placeholder "Any text", _type "value",value state.inputValue,onInput \e -> dispatch (SetInput (unsafeEventValue e))] [] [ input [className "form-control", _id "id_password", name "password", placeholder "Any text", _type "value",value state.inputValue,onInput \e -> dispatch (SetInput (unsafeEventValue e))]
, div [className "clearfix"] [] , div [className "clearfix"] []
] ]
, button [className "btn btn-primary", _type "button"] [text "Create and Add"] , button [className "btn btn-primary", _type "button"] [text "Create and Add"]
......
...@@ -60,7 +60,7 @@ ngramsItemSpec = simpleSpec performAction render ...@@ -60,7 +60,7 @@ ngramsItemSpec = simpleSpec performAction render
, checked $ getter _._type state.term == MapTerm , checked $ getter _._type state.term == MapTerm
, title "Mark as completed" , title "Mark as completed"
, onChange $ dispatch <<< ( const $ SetMap $ not (getter _._type state.term == MapTerm)) , onChange $ dispatch <<< ( const $ SetMap $ not (getter _._type state.term == MapTerm))
] [] ]
checkbox_stop = checkbox_stop =
input input
[ _type "checkbox" [ _type "checkbox"
...@@ -68,7 +68,7 @@ ngramsItemSpec = simpleSpec performAction render ...@@ -68,7 +68,7 @@ ngramsItemSpec = simpleSpec performAction render
, checked $ getter _._type state.term == StopTerm , checked $ getter _._type state.term == StopTerm
, title "Mark as completed" , title "Mark as completed"
, onChange $ dispatch <<< ( const $ SetStop $ not (getter _._type state.term == StopTerm)) , onChange $ dispatch <<< ( const $ SetStop $ not (getter _._type state.term == StopTerm))
] [] ]
dispTerm :: String -> TermType -> ReactElement dispTerm :: String -> TermType -> ReactElement
......
module Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable where module Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsTable where
import CSS.TextAlign (center, textAlign)
import Data.Array (filter, fold, toUnfoldable) import Data.Array (filter, fold, toUnfoldable)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Lens (Lens', Prism', lens, over, prism) import Data.Lens (Lens', Prism', lens, over, prism)
import Data.List (List) import Data.List (List)
import Data.Tuple (Tuple(..), uncurry) import Data.Tuple (Tuple(..), uncurry)
import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsItem as NI import Gargantext.Pages.Corpus.Doc.Facets.Terms.NgramsItem as NI
import Prelude (class Eq, class Ord, class Show, Unit, bind, map, not, pure, show, void, ($), (*), (+), (-), (/), (<), (<$>), (<>), (==), (>), (>=), (>>=)) import Prelude (class Eq, class Ord, class Show, map, show, void, ($), (*), (+), (-), (/), (<), (<>), (==), (>), (>=))
import React (ReactElement) import React (ReactElement)
import React.DOM hiding (style) import React.DOM hiding (style, map)
import React.DOM.Props (_id, _type, className, href, name, onChange, onClick, onInput, placeholder, scope, selected, style, value) import React.DOM.Props (_id, _type, className, href, name, onChange, onClick, onInput, placeholder, scope, selected, style, value)
import Thermite (PerformAction, Spec, _render, cotransform, focus, foreach, modifyState, withState) import Thermite (PerformAction, Spec, _render, cotransform, focus, foreach, modifyState, withState)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
...@@ -52,8 +52,6 @@ _ItemAction = prism (uncurry ItemAction) \ta -> ...@@ -52,8 +52,6 @@ _ItemAction = prism (uncurry ItemAction) \ta ->
_ -> Left ta _ -> Left ta
performAction :: forall props. PerformAction State props Action performAction :: forall props. PerformAction State props Action
performAction _ _ _ = void do
modifyState \(State state) -> State $ state
performAction (ChangePageSize ps) _ _ = void (cotransform (\state -> changePageSize ps state )) performAction (ChangePageSize ps) _ _ = void (cotransform (\state -> changePageSize ps state ))
...@@ -69,7 +67,10 @@ performAction (ChangeString c) _ _ = void do ...@@ -69,7 +67,10 @@ performAction (ChangeString c) _ _ = void do
performAction (SetInput s) _ _ = void do performAction (SetInput s) _ _ = void do
modifyState \(State state) -> State $ state { search = s } modifyState \(State state) -> State $ state { search = s }
tableSpec :: forall props .Spec State props Action -> Spec eff State props Action performAction _ _ _ = void do
modifyState \(State state) -> State $ state
tableSpec :: forall props .Spec State props Action -> Spec State props Action
tableSpec = over _render \render dispatch p (State s) c -> tableSpec = over _render \render dispatch p (State s) c ->
[div [className "container-fluid"] [div [className "container-fluid"]
[ [
...@@ -97,7 +98,7 @@ tableSpec = over _render \render dispatch p (State s) c -> ...@@ -97,7 +98,7 @@ tableSpec = over _render \render dispatch p (State s) c ->
, _type "value" , _type "value"
,value s.search ,value s.search
,onInput \e -> dispatch (SetInput (unsafeEventValue e)) ,onInput \e -> dispatch (SetInput (unsafeEventValue e))
] [] ]
] ]
......
module Gargantext.Pages.Corpus.User.Brevets where module Gargantext.Pages.Corpus.User.Brevets where
import Prelude
import Prelude (id, void)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec) import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
...@@ -14,8 +13,7 @@ data Action = NoOp ...@@ -14,8 +13,7 @@ data Action = NoOp
performAction :: forall props. PerformAction State props Action performAction :: forall props. PerformAction State props Action
performAction NoOp _ _ = void do performAction NoOp _ _ = void do
modifyState id modifyState identity
brevetsSpec :: forall props. Spec State props Action brevetsSpec :: forall props. Spec State props Action
brevetsSpec = simpleSpec performAction render brevetsSpec = simpleSpec performAction render
......
module Gargantext.Pages.Corpus.User.Users.Specs.Documents where module Gargantext.Pages.Corpus.User.Users.Specs.Documents where
import Prelude (id, void) import Prelude
import React.DOM (table, tbody, td, text, th, thead, tr) import React.DOM (table, tbody, td, text, th, thead, tr)
import React.DOM.Props (className, scope) import React.DOM.Props (className, scope)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec) import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
...@@ -15,9 +15,7 @@ data Action = NoOp ...@@ -15,9 +15,7 @@ data Action = NoOp
performAction :: forall props. PerformAction State props Action performAction :: forall props. PerformAction State props Action
performAction NoOp _ _ = void do performAction NoOp _ _ = void do
modifyState id modifyState identity
publicationSpec :: forall props. Spec State props Action publicationSpec :: forall props. Spec State props Action
publicationSpec = simpleSpec performAction render publicationSpec = simpleSpec performAction render
......
...@@ -7,7 +7,7 @@ import Data.Maybe (Maybe(..)) ...@@ -7,7 +7,7 @@ import Data.Maybe (Maybe(..))
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Prelude (($), (<<<)) import Prelude (($), (<<<))
import React (ReactElement) import React (ReactElement)
import React.DOM (div, h3, h1, li, span, text, ul, img) import React.DOM (div, h3, img, li, span, text, ul)
import React.DOM.Props (_id, className, src) import React.DOM.Props (_id, className, src)
import Thermite (Render) import Thermite (Render)
...@@ -21,7 +21,7 @@ render dispatch _ state _ = ...@@ -21,7 +21,7 @@ render dispatch _ state _ =
Nothing -> display "User not found" [] Nothing -> display "User not found" []
] ]
display :: forall props. String -> Array ReactElement -> Array ReactElement display :: String -> Array ReactElement -> Array ReactElement
display title elems = display title elems =
[ div [className "container-fluid"] [ div [className "container-fluid"]
[ div [className "row", _id "user-page-header"] [ div [className "row", _id "user-page-header"]
...@@ -33,7 +33,7 @@ display title elems = ...@@ -33,7 +33,7 @@ display title elems =
[ div [className "col-md-12"] [ div [className "col-md-12"]
[ div [className "row"] [ div [className "row"]
[ div [className "col-md-2"] [ div [className "col-md-2"]
[ img [src "/images/Gargantextuel-212x300.jpg"] [] ] [ img [src "/images/Gargantextuel-212x300.jpg"] ]
, div [className "col-md-1"] [] , div [className "col-md-1"] []
, div [className "col-md-8"] elems , div [className "col-md-8"] elems
] ]
...@@ -58,10 +58,10 @@ userInfos (HyperData user) = ...@@ -58,10 +58,10 @@ userInfos (HyperData user) =
checkMaybe (Nothing) = "" checkMaybe (Nothing) = ""
checkMaybe (Just a) = a checkMaybe (Just a) = a
listElement :: forall props. Array ReactElement -> ReactElement listElement :: Array ReactElement -> ReactElement
listElement = li [className "list-group-item justify-content-between"] listElement = li [className "list-group-item justify-content-between"]
infoRender :: forall props. Tuple String String -> Array ReactElement infoRender :: Tuple String String -> Array ReactElement
infoRender (Tuple title content) = infoRender (Tuple title content) =
[ span [] [text title] [ span [] [text title]
, span [className "badge badge-default badge-pill"] [text content] , span [className "badge badge-default badge-pill"] [text content]
......
module Gargantext.Pages.Folder where module Gargantext.Pages.Folder where
import Prelude (id, void) import Prelude
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec) import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
...@@ -14,8 +14,7 @@ data Action = NoOp ...@@ -14,8 +14,7 @@ data Action = NoOp
performAction :: forall props. PerformAction State props Action performAction :: forall props. PerformAction State props Action
performAction NoOp _ _ = void do performAction NoOp _ _ = void do
modifyState id modifyState identity
projets :: forall props. Spec State props Action projets :: forall props. Spec State props Action
projets = simpleSpec performAction render projets = simpleSpec performAction render
......
module Gargantext.Pages.Home.Actions where module Gargantext.Pages.Home.Actions where
import Prelude hiding (div) import Prelude hiding (div)
import Gargantext.Components.Lang.Landing.EnUS as En import Effect.Class (liftEffect)
import Gargantext.Components.Lang.Landing.FrFR as Fr import Gargantext.Pages.Home.States (State)
import Gargantext.Components.Data.Landing (BlockText(..), BlockTexts(..), Button(..), LandingData(..)) import Routing.Hash (setHash)
import Gargantext.Components.Data.Lang (Lang(..)) import Thermite (PerformAction, modifyState)
import Gargantext.Pages.Home.States (State(..))
import React (ReactElement)
import React.DOM (a, div, h3, i, img, p, span, text)
import React.DOM.Props (Props, _id, aria, className, href, src, target, title)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
data Action data Action
= NoOp = NoOp
...@@ -31,11 +23,11 @@ performAction Documentation _ _ = void do ...@@ -31,11 +23,11 @@ performAction Documentation _ _ = void do
modifyState \state -> state modifyState \state -> state
performAction Enter _ _ = void do performAction Enter _ _ = void do
lift $ setHash "/search" liftEffect $ setHash "/search"
modifyState \state -> state modifyState \state -> state
performAction Login _ _ = void do performAction Login _ _ = void do
lift $ setHash "/login" liftEffect $ setHash "/login"
modifyState \state -> state modifyState \state -> state
performAction SignUp _ _ = void do performAction SignUp _ _ = void do
......
...@@ -6,13 +6,13 @@ import Gargantext.Components.Lang.Landing.EnUS as En ...@@ -6,13 +6,13 @@ import Gargantext.Components.Lang.Landing.EnUS as En
import Gargantext.Components.Lang.Landing.FrFR as Fr import Gargantext.Components.Lang.Landing.FrFR as Fr
import Gargantext.Components.Data.Landing (BlockText(..), BlockTexts(..), Button(..), LandingData(..)) import Gargantext.Components.Data.Landing (BlockText(..), BlockTexts(..), Button(..), LandingData(..))
import Gargantext.Components.Data.Lang (Lang(..)) import Gargantext.Components.Data.Lang (Lang(..))
import Gargantext.Pages.Home.States (State(..)) import Gargantext.Pages.Home.States (State)
import Gargantext.Pages.Home.Actions (Action(..), performAction) import Gargantext.Pages.Home.Actions (Action, performAction)
import React (ReactElement) import React (ReactElement)
import React.DOM (a, div, h3, i, img, p, span, text) import React.DOM (a, div, h3, i, img, p, span, text)
import React.DOM.Props (Props, _id, aria, className, href, src, target, title) import React.DOM.Props (Props, _id, aria, className, href, src, target, title)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec) import Thermite (Render, Spec, simpleSpec)
-- Layout | -- Layout |
...@@ -73,7 +73,7 @@ jumboTitle (LandingData hd) b = div jumbo ...@@ -73,7 +73,7 @@ jumboTitle (LandingData hd) b = div jumbo
[ div [_id "logo-designed" ] [ div [_id "logo-designed" ]
[ img [ src "images/logo.png" [ img [ src "images/logo.png"
, title hd.logoTitle , title hd.logoTitle
] [] ]
] ]
] ]
] ]
...@@ -82,7 +82,7 @@ jumboTitle (LandingData hd) b = div jumbo ...@@ -82,7 +82,7 @@ jumboTitle (LandingData hd) b = div jumbo
, _id "funnyimg" , _id "funnyimg"
, title hd.imageTitle , title hd.imageTitle
] ]
[]
] ]
] ]
] ]
...@@ -99,6 +99,5 @@ imageEnter (LandingData hd) action = div [className "row"] ...@@ -99,6 +99,5 @@ imageEnter (LandingData hd) action = div [className "row"]
, title hd.imageTitle , title hd.imageTitle
, action , action
] ]
[]
] ]
] ]
module Gargantext.Pages.Layout.Specs.AddCorpus.Actions where module Gargantext.Pages.Layout.Specs.AddCorpus.Actions where
import Gargantext.Pages.Layout.Specs.AddCorpus.States
import Prelude hiding (div) import Prelude hiding (div)
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, jsonEmptyObject, (.?), (:=), (~>)) import Affjax (defaultRequest, request)
import Affjax.RequestBody (RequestBody(..))
import Affjax.RequestHeader (RequestHeader(..))
import Control.Monad.Cont.Trans (lift)
import Data.Argonaut (class EncodeJson, decodeJson, encodeJson, jsonEmptyObject, (:=), (~>))
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.HTTP.Method (Method(..)) import Data.HTTP.Method (Method(..))
import Data.Lens (over)
import Data.Maybe (Maybe(Just)) import Data.Maybe (Maybe(Just))
import Data.MediaType.Common (applicationJSON) import Data.MediaType.Common (applicationJSON)
import Effect.Aff (Aff, attempt)
import Effect.Aff.Class (liftAff)
import Effect.Class (liftEffect)
import Effect.Console (log)
import Gargantext.Components.Modals.Modal (modalHide) import Gargantext.Components.Modals.Modal (modalHide)
import Gargantext.Pages.Layout.Specs.AddCorpus.States import Routing.Hash (setHash)
import Thermite (PerformAction, modifyState)
import React (ReactElement)
import React.DOM (button, div, h3, h5, li, span, text, ul)
import React.DOM.Props (_data, _id, _type, aria, className, onClick, role)
import Thermite (PerformAction, Render, Spec, _render, cotransform, modifyState, simpleSpec)
data Action data Action
= NoOp = NoOp
...@@ -26,7 +29,7 @@ data Action ...@@ -26,7 +29,7 @@ data Action
performAction :: forall props. PerformAction State props Action performAction :: forall props. PerformAction State props Action
performAction NoOp _ _ = void do performAction NoOp _ _ = void do
modifyState id modifyState identity
performAction (SelectDatabase selected) _ _ = void do performAction (SelectDatabase selected) _ _ = void do
modifyState \( state) -> state { select_database = selected } modifyState \( state) -> state { select_database = selected }
...@@ -37,14 +40,14 @@ performAction (UnselectDatabase unselected) _ _ = void do ...@@ -37,14 +40,14 @@ performAction (UnselectDatabase unselected) _ _ = void do
performAction (LoadDatabaseDetails) _ _ = void do performAction (LoadDatabaseDetails) _ _ = void do
res <- lift $ getDatabaseDetails $ QueryString { query_query: "string",query_name: ["Pubmed"]} res <- lift $ getDatabaseDetails $ QueryString { query_query: "string",query_name: ["Pubmed"]}
case res of case res of
Left err -> cotransform $ \(state) -> state Left err -> modifyState $ \(state) -> state
Right resData -> do Right resData -> do
cotransform $ \(state) -> state {response = resData} modifyState $ \(state) -> state {response = resData}
performAction GO _ _ = void do performAction GO _ _ = void do
lift $ setHash "/corpus" lift $ setHash "/corpus"
_ <- liftEff $ modalHide "addCorpus" _ <- liftEffect $ modalHide "addCorpus"
modifyState id modifyState identity
newtype QueryString = QueryString newtype QueryString = QueryString
...@@ -74,22 +77,24 @@ instance encodeJsonQueryString :: EncodeJson QueryString where ...@@ -74,22 +77,24 @@ instance encodeJsonQueryString :: EncodeJson QueryString where
getDatabaseDetails :: QueryString -> Aff (Either String (Array Response)) getDatabaseDetails :: QueryString -> Aff (Either String (Array Response))
getDatabaseDetails reqBody = do getDatabaseDetails reqBody = do
let token = "eyJ0eXAiOiJKV1QiLCJhbGciOiJIUzI1NiJ9.eyJleHAiOjE1MTk5OTg1ODMsInVzZXJfaWQiOjUsImVtYWlsIjoiYWxleGFuZHJlLmRlbGFub2VAaXNjcGlmLmZyIiwidXNlcm5hbWUiOiJkZXZlbG9wZXIifQ.Os-3wuFNSmRIxCZi98oFNBu2zqGc0McO-dgDayozHJg" let token = "eyJ0eXAiOiJKV1QiLCJhbGciOiJIUzI1NiJ9.eyJleHAiOjE1MTk5OTg1ODMsInVzZXJfaWQiOjUsImVtYWlsIjoiYWxleGFuZHJlLmRlbGFub2VAaXNjcGlmLmZyIiwidXNlcm5hbWUiOiJkZXZlbG9wZXIifQ.Os-3wuFNSmRIxCZi98oFNBu2zqGc0McO-dgDayozHJg"
affResp <- liftAff $ attempt $ affjax defaultRequest affResp <- liftAff $ attempt $ request $ defaultRequest
{ method = Left POST { method = Left POST
, url ="http://localhost:8009/count" , url ="http://localhost:8009/count"
, headers = [ ContentType applicationJSON , headers = [ ContentType applicationJSON
, Accept applicationJSON , Accept applicationJSON
-- , RequestHeader "Authorization" $ "Bearer " <> token -- , RequestHeader "Authorization" $ "Bearer " <> token
] ]
, content = Just $ encodeJson reqBody , content = Just $ Json $ encodeJson reqBody
} }
case affResp of case affResp of
Left err -> do Left err -> do
liftAff $ log $ "error" <> show err liftEffect $ log $ "error" <> show err
pure $ Left $ show err pure $ Left $ show err
Right a -> do Right a -> do
liftAff $ log $ "POST method Completed" liftEffect $ log $ "POST method Completed"
liftAff $ log $ "GET /api response: " <> show a.response liftEffect $ log $ "GET /api response: " <> show a.body
let res = decodeJson a.response res <- case a.body of
Left err -> []
Right d -> decodeJson d
pure res pure res
module Gargantext.Pages.Layout.Specs.Search where module Gargantext.Pages.Layout.Specs.Search where
import Prelude hiding (div) import Prelude hiding (div)
import React.DOM (br', button, div, h3, input, text, i, span, img)
import React.DOM.Props (_id, _type, className, name, onClick, onInput, placeholder, value, aria, src, title) import Effect.Class (liftEffect)
import React.DOM (br', button, div, input, text)
import React.DOM.Props (_id, _type, className, name, onClick, onInput, placeholder, value)
import Routing.Hash (setHash)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec) import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Pages.Home as L
type State = type State =
{ {
...@@ -28,7 +30,7 @@ data Action ...@@ -28,7 +30,7 @@ data Action
performAction :: forall props. PerformAction State props Action performAction :: forall props. PerformAction State props Action
performAction NoOp _ _ = void do performAction NoOp _ _ = void do
modifyState id modifyState identity
performAction (SetQuery q) _ _ = void do performAction (SetQuery q) _ _ = void do
...@@ -36,8 +38,8 @@ performAction (SetQuery q) _ _ = void do ...@@ -36,8 +38,8 @@ performAction (SetQuery q) _ _ = void do
performAction GO _ _ = void do performAction GO _ _ = void do
lift $ setHash "/addCorpus" liftEffect $ setHash "/addCorpus"
modifyState id modifyState identity
unsafeEventValue :: forall event. event -> String unsafeEventValue :: forall event. event -> String
...@@ -53,8 +55,8 @@ searchSpec = simpleSpec performAction render ...@@ -53,8 +55,8 @@ searchSpec = simpleSpec performAction render
[ div [className "jumbotron" ] [ div [className "jumbotron" ]
[ div [className "row" ] [ div [className "row" ]
[ div [className "col-md-10" ] [ div [className "col-md-10" ]
[ br' [] [ br'
, br' [] , br'
, div [ className "form-group"] , div [ className "form-group"]
[ input [ className "form-control" [ input [ className "form-control"
, _id "id_password" , _id "id_password"
...@@ -63,16 +65,16 @@ searchSpec = simpleSpec performAction render ...@@ -63,16 +65,16 @@ searchSpec = simpleSpec performAction render
, _type "text" , _type "text"
, value state.query , value state.query
, onInput \e -> dispatch (SetQuery (unsafeEventValue e)) , onInput \e -> dispatch (SetQuery (unsafeEventValue e))
] [] ]
, br'[] , br'
] ]
] ]
, div [ className "col-md-2"] , div [ className "col-md-2"]
[ br' [] [ br'
, br' [] , br'
, button [onClick \_ -> dispatch GO] [text "GO"] , button [onClick \_ -> dispatch GO] [text "GO"]
] ]
, br' [] , br'
] ]
] ]
] ]
......
...@@ -3,11 +3,15 @@ module Gargantext.Router where ...@@ -3,11 +3,15 @@ module Gargantext.Router where
import Prelude import Prelude
import Control.Alt ((<|>)) import Control.Alt ((<|>))
import Effect (Effect)
import Effect.Class (liftEffect)
import Data.Int (floor) import Data.Int (floor)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Routing.Match (Match) import Effect (Effect)
import Effect.Class (liftEffect)
import Effect.Console (log)
import Routing.Match (Match, lit, num)
import Web.HTML (window)
import Web.HTML.Window (localStorage)
import Web.Storage.Storage (getItem)
data Routes data Routes
= Home = Home
...@@ -60,16 +64,16 @@ routing = ...@@ -60,16 +64,16 @@ routing =
routeHandler :: (Maybe Routes -> Routes -> Effect Unit) -> Maybe Routes -> Routes -> Effect Unit routeHandler :: (Maybe Routes -> Routes -> Effect Unit) -> Maybe Routes -> Routes -> Effect Unit
routeHandler dispatchAction old new = do routeHandler dispatchAction old new = do
liftEff $ log $ "change route : " <> show new liftEffect $ log $ "change route : " <> show new
w <- window w <- window
ls <- localStorage w ls <- localStorage w
token <- getItem "accessToken" ls token <- getItem "accessToken" ls
let tkn = token let tkn = token
liftEff $ log $ "JWToken : " <> show tkn liftEffect $ log $ "JWToken : " <> show tkn
case tkn of case tkn of
Nothing -> do Nothing -> do
dispatchAction old new dispatchAction old new
liftEff $ log $ "called SignIn Route :" liftEffect $ log $ "called SignIn Route :"
Just t -> do Just t -> do
dispatchAction old new dispatchAction old new
liftEff $ log $ "called Route : " <> show new liftEffect $ log $ "called Route : " <> show new
...@@ -2,13 +2,14 @@ module Gargantext.Utils.DecodeMaybe where ...@@ -2,13 +2,14 @@ module Gargantext.Utils.DecodeMaybe where
import Prelude import Prelude
import Data.Argonaut (class DecodeJson, JObject, getFieldOptional) import Data.Argonaut (class DecodeJson, Json, getFieldOptional)
import Data.Either (Either) import Data.Either (Either)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Foreign.Object (Object)
foreign import isNull :: forall a. a -> Boolean foreign import isNull :: forall a. a -> Boolean
getFieldOptional' :: forall a. DecodeJson a => JObject -> String -> Either String (Maybe a) getFieldOptional' :: forall t9. DecodeJson t9 => Object Json -> String -> Either String (Maybe t9)
getFieldOptional' o s = (case _ of getFieldOptional' o s = (case _ of
Just v -> if isNull v then Nothing else v Just v -> if isNull v then Nothing else v
Nothing -> Nothing Nothing -> Nothing
......
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