Use {} instead of forall props in specs

parent 246ab19a
......@@ -52,7 +52,7 @@ data Action
| SetPassword String
performAction :: forall props. PerformAction State props Action
performAction :: PerformAction State {} Action
performAction NoOp _ _ = void do
modifyState identity
......@@ -107,13 +107,13 @@ modalSpec sm t = over _render \render d p s c ->
]
]
spec' :: forall props. Spec State props Action
spec' :: Spec State {} Action
spec' = modalSpec true "Login" renderSpec
renderSpec :: forall props. Spec State props Action
renderSpec :: Spec State {} Action
renderSpec = simpleSpec performAction render
where
render :: Render State props Action
render :: Render State {} Action
render dispatch _ (State state) _ =
[
div [className "row"]
......
......@@ -33,7 +33,7 @@ type State = FTree
initialState :: State
initialState = NLeaf (Tuple "" "")
performAction :: forall props. PerformAction State props Action
performAction :: PerformAction State {} Action
performAction (ToggleFolder i) _ _ = void $
cotransform (\td -> toggleNode i td)
......@@ -89,10 +89,10 @@ nodeOptionsView activated = case activated of
false -> []
treeview :: forall props. Spec State props Action
treeview :: Spec State {} Action
treeview = simpleSpec performAction render
where
render :: Render State props Action
render :: Render State {} Action
render dispatch _ state _ =
[div [className "tree"] [toHtml dispatch state]]
......
......@@ -24,15 +24,15 @@ type Corpus = { title :: String
initialState :: State
initialState = Tab.initialState
spec' :: forall props. Spec Tab.State props Tab.Action
spec' :: Spec Tab.State {} Tab.Action
spec' = fold [ corpusSpec
, Tab.tab1
]
corpusSpec :: forall props. Spec Tab.State props Tab.Action
corpusSpec :: Spec Tab.State {} Tab.Action
corpusSpec = simpleSpec defaultPerformAction render
where
render :: Render Tab.State props Tab.Action
render :: Render Tab.State {} Tab.Action
render dispatch _ state _ =
[ div [className "row"]
[ div [className "col-md-3"] [ h3 [] [text corpus.title] ]
......
......@@ -27,7 +27,7 @@ data Action
| SetInput String
performAction :: forall props. PerformAction State props Action
performAction :: PerformAction State {} Action
performAction NoOp _ _ = pure unit
performAction (ChangeString ps) _ _ = pure unit
......@@ -39,10 +39,10 @@ performAction (SetInput ps) _ _ = void do
docview :: forall props. Spec State props Action
docview :: Spec State {} Action
docview = simpleSpec performAction render
where
render :: Render State props Action
render :: Render State {} Action
render dispatch _ state _ =
[
div [className "container1"]
......
......@@ -14,13 +14,12 @@ initialState = D.tdata
type Action = D.Action
authorSpec :: forall props. Spec State props Action
authorSpec :: Spec State {} Action
authorSpec = simpleSpec defaultPerformAction render
where
render :: Render State props Action
render :: Render State {} Action
render dispatch _ state _ =
[ h3 [] [text "AuthorView"]]
authorspec' :: forall props. Spec State props Action
authorspec' :: Spec State {} Action
authorspec' = fold [authorSpec, D.layoutDocview]
......@@ -19,10 +19,10 @@ data Action = None
initialState :: State
initialState = unit
performAction :: forall props. PerformAction State props Action
performAction :: PerformAction State {} Action
performAction _ _ _ = pure unit
render :: forall props. Render State props Action
render :: Render State {} Action
render dispatch _ state _ = [
h1 [] [text "IMT DashBoard"]
, div [className "row"] [ div [className "col-md-9 content"] [chart globalPublis]
......@@ -104,5 +104,5 @@ distriBySchool = Options { mainTitle : "School production in 2017"
}
layoutDashboard :: forall props. Spec State props Action
layoutDashboard :: Spec State {} Action
layoutDashboard = simpleSpec performAction render
......@@ -133,17 +133,17 @@ instance decodeResponse :: DecodeJson Response where
-- | Filter
filterSpec :: forall props. Spec State props Action
filterSpec :: Spec State {} Action
filterSpec = simpleSpec defaultPerformAction render
where
render d p s c = [div [] [ text " Filter "
, input []
]]
layoutDocview :: forall props. Spec State props Action
layoutDocview :: Spec State {} Action
layoutDocview = simpleSpec performAction render
where
render :: Render State props Action
render :: Render State {} Action
render dispatch _ state@(TableData d) _ =
[ div [className "container1"]
[ div [className "row"]
......@@ -177,7 +177,7 @@ layoutDocview = simpleSpec performAction render
]
performAction :: forall props. PerformAction State props Action
performAction :: PerformAction State {} Action
performAction (ChangePageSize ps) _ _ = void (cotransform (\state -> changePageSize ps state ))
performAction (ChangePage p) _ _ = void (cotransform (\(TableData td) -> TableData $ td { currentPage = p} ))
......
......@@ -54,10 +54,10 @@ initialState = State
, selectedNode : Nothing
}
graphSpec :: forall props. Spec State props Action
graphSpec :: Spec State {} Action
graphSpec = simpleSpec performAction render
performAction :: forall props. PerformAction State props Action
performAction :: PerformAction State {} Action
performAction (LoadGraph fp) _ _ = void do
_ <- liftEffect $ log fp
case fp of
......@@ -97,7 +97,7 @@ convert (GraphData r) = SigmaGraphData { nodes, edges}
edges = map edgeFn r.edges
edgeFn (Edge e) = sigmaEdge {id : e.id_, source : e.source, target : e.target}
render :: forall props. Render State props Action
render :: Render State {} Action
render d p (State s) c =
[ select [ onChange $ \e -> d $ LoadGraph (unsafeCoerce e).target.value, value s.filePath]
[ option [value ""] [text ""]
......@@ -296,10 +296,10 @@ dispLegend ary = div [] $ map dl ary
]
specOld :: forall props. Spec State props Action
specOld :: Spec State {} Action
specOld = simpleSpec performAction render'
where
render' :: Render State props Action
render' :: Render State {} Action
render' d _ (State st) _ =
[ div [className "row"] [
div [className "col-md-12", style {marginTop : "21px", marginBottom : "21px"}]
......
......@@ -16,12 +16,12 @@ initialState = D.tdata
type Action = D.Action
sourceSpec :: forall props. Spec State props Action
sourceSpec :: Spec State {} Action
sourceSpec = simpleSpec defaultPerformAction render
where
render :: Render State props Action
render :: Render State {} Action
render dispatch _ state _ =
[ h3 [] [text "Source view"]]
sourcespec' :: forall props. Spec State props Action
sourcespec' :: Spec State {} Action
sourcespec' = fold [sourceSpec, D.layoutDocview]
......@@ -19,21 +19,21 @@ import Thermite (Spec, focus)
tab1 :: forall props. Spec State props Action
tab1 :: Spec State {} Action
tab1 = Tab.tabs _tablens _tabAction $ fromFoldable [ Tuple "Doc View" docPageSpec
, Tuple "Author View" authorPageSpec
, Tuple "Source View" sourcePageSpec
, Tuple "Terms View" termsPageSpec
]
docPageSpec :: forall props. Spec State props Action
docPageSpec :: Spec State {} Action
docPageSpec = focus _doclens _docAction DV.layoutDocview
authorPageSpec :: forall props. Spec State props Action
authorPageSpec :: Spec State {} Action
authorPageSpec = focus _authorlens _authorAction AV.authorspec'
sourcePageSpec :: forall props. Spec State props Action
sourcePageSpec :: Spec State {} Action
sourcePageSpec = focus _sourcelens _sourceAction SV.sourcespec'
termsPageSpec :: forall props. Spec State props Action
termsPageSpec :: Spec State {} Action
termsPageSpec = focus _termslens _termsAction TV.termSpec'
......@@ -17,12 +17,12 @@ initialState = D.tdata
type Action = D.Action
termsSpec :: forall props. Spec State props Action
termsSpec :: Spec State {} Action
termsSpec = simpleSpec defaultPerformAction render
where
render :: Render State props Action
render :: Render State {} Action
render dispatch _ state _ =
[ h3 [] [text "Terms view"]]
termSpec' :: forall props. Spec State props Action
termSpec' :: Spec State {} Action
termSpec' = fold [termsSpec, D.layoutDocview]
......@@ -33,17 +33,17 @@ data Action
= SetMap Boolean
| SetStop Boolean
performAction :: forall props. PerformAction State props Action
performAction :: PerformAction State {} Action
performAction (SetMap b) _ _ = void do
modifyState \(State s) -> State s {term = setter (_{_type = (if b then MapTerm else None)}) s.term}
performAction (SetStop b) _ _ = void do
modifyState \(State s) -> State s {term = setter (_{_type = (if b then StopTerm else None)}) s.term}
ngramsItemSpec :: forall props. Spec State props Action
ngramsItemSpec :: Spec State {} Action
ngramsItemSpec = simpleSpec performAction render
where
render :: Render State props Action
render :: Render State {} Action
render dispatch _ (State state) _ =
[
tr []
......
......@@ -51,7 +51,7 @@ _ItemAction = prism (uncurry ItemAction) \ta ->
ItemAction i a -> Right (Tuple i a)
_ -> Left ta
performAction :: forall props. PerformAction State props Action
performAction :: PerformAction State {} Action
performAction (ChangePageSize ps) _ _ = void (cotransform (\state -> changePageSize ps state ))
......@@ -70,7 +70,7 @@ performAction (SetInput s) _ _ = void do
performAction _ _ _ = void do
modifyState \(State state) -> State $ state
tableSpec :: forall props .Spec State props Action -> Spec State props Action
tableSpec :: Spec State {} Action -> Spec State {} Action
tableSpec = over _render \render dispatch p (State s) c ->
[div [className "container-fluid"]
[
......@@ -147,7 +147,7 @@ tableSpec = over _render \render dispatch p (State s) c ->
]
]
ngramsTableSpec :: forall props . Spec State props Action
ngramsTableSpec :: Spec State {} Action
ngramsTableSpec = container $ fold
[ tableSpec $ withState \st ->
focus _itemsList _ItemAction $
......
......@@ -11,13 +11,13 @@ initialState = ""
data Action = NoOp
performAction :: forall props. PerformAction State props Action
performAction :: PerformAction State {} Action
performAction NoOp _ _ = void do
modifyState identity
brevetsSpec :: forall props. Spec State props Action
brevetsSpec :: Spec State {} Action
brevetsSpec = simpleSpec performAction render
where
render :: Render State props Action
render :: Render State {} Action
render dispatch _ state _ =
[]
......@@ -17,7 +17,7 @@ getUser :: Int -> Aff (Either String User)
getUser id = get $ "http://localhost:8008/node/" <> show id
performAction :: forall props. PerformAction State props Action
performAction :: PerformAction State {} Action
performAction NoOp _ _ = void do
modifyState identity
performAction (FetchUser userId) _ _ = void do
......
......@@ -9,5 +9,5 @@ import Thermite (Spec, simpleSpec)
import Gargantext.Pages.Corpus.User.Users.Types (Action, State)
import Gargantext.Pages.Corpus.User.Users.API (performAction)
layoutUser :: forall props. Spec State props Action
layoutUser :: Spec State {} Action
layoutUser = simpleSpec performAction render
......@@ -13,14 +13,14 @@ initialState = ""
data Action = NoOp
performAction :: forall props. PerformAction State props Action
performAction :: PerformAction State {} Action
performAction NoOp _ _ = void do
modifyState identity
publicationSpec :: forall props. Spec State props Action
publicationSpec :: Spec State {} Action
publicationSpec = simpleSpec performAction render
where
render :: Render State props Action
render :: Render State {} Action
render dispatch _ state _ =
[ table [ className "table"]
[ thead [ className "thead-dark"]
......
......@@ -12,7 +12,7 @@ import React.DOM.Props (_id, className, src)
import Thermite (Render)
render :: forall props. Render State props Action
render :: Render State {} Action
render dispatch _ state _ =
[
div [className "col-md-12"]
......
......@@ -20,16 +20,15 @@ import Gargantext.Pages.Folder as PS
import Gargantext.Components.Tab (tabs)
import Thermite (Spec, focus)
brevetSpec :: forall props. Spec State props Action
brevetSpec :: Spec State {} Action
brevetSpec = focus _brevetslens _brevetsAction B.brevetsSpec
projectSpec :: forall props. Spec State props Action
projectSpec :: Spec State {} Action
projectSpec = focus _projectslens _projectsAction PS.projets
facets :: forall props. Spec State props Action
facets :: Spec State {} Action
facets = tabs _tablens _tabAction $ fromFoldable
[ Tuple "Publications (12)" publicationSpec
, Tuple "Brevets (2)" brevetSpec
, Tuple "Projets IMT (5)" projectSpec
]
]
......@@ -32,7 +32,7 @@ _pubAction = prism PublicationA \ action ->
PublicationA laction -> Right laction
_-> Left action
publicationSpec :: forall props. Spec State props Action
publicationSpec :: Spec State {} Action
publicationSpec = focus _publens _pubAction P.publicationSpec
_brevetslens :: Lens' State B.State
......
......@@ -12,13 +12,13 @@ initialState = ""
data Action = NoOp
performAction :: forall props. PerformAction State props Action
performAction :: PerformAction State {} Action
performAction NoOp _ _ = void do
modifyState identity
projets :: forall props. Spec State props Action
projets :: Spec State {} Action
projets = simpleSpec performAction render
where
render :: Render State props Action
render :: Render State {} Action
render dispatch _ state _ =
[]
......@@ -15,7 +15,7 @@ data Action
| SignUp
performAction :: forall props. PerformAction State props Action
performAction :: PerformAction State {} Action
performAction NoOp _ _ = void do
modifyState \state -> state
......
......@@ -17,16 +17,16 @@ import Thermite (Render, Spec, simpleSpec)
-- Layout |
layoutLanding :: forall props. Lang -> Spec State props Action
layoutLanding :: Lang -> Spec State {} Action
layoutLanding FR = layoutLanding' Fr.landingData
layoutLanding EN = layoutLanding' En.landingData
------------------------------------------------------------------------
layoutLanding' :: forall props. LandingData -> Spec State props Action
layoutLanding' :: LandingData -> Spec State {} Action
layoutLanding' hd = simpleSpec performAction render
where
render :: Render State props Action
render :: Render State {} Action
render dispatch _ state _ =
[ div [ className "container1" ] [ jumboTitle hd false ]
, div [ className "container1" ] [] -- put research here
......
......@@ -49,7 +49,7 @@ data Action
| NgramsA NG.Action
performAction :: forall props. PerformAction AppState props Action
performAction :: PerformAction AppState {} Action
performAction (SetRoute route) _ _ = void do
modifyState $ _ {currentRoute = pure route}
performAction (Search s) _ _ = void do
......
......@@ -29,7 +29,7 @@ import React.DOM.Props (_data, _id, _type, aria, className, href, onChange, onCl
import Thermite (Render, Spec, _render, defaultPerformAction, defaultRender, focus, simpleSpec, withState)
import Unsafe.Coerce (unsafeCoerce)
layoutSpec :: forall props. Spec AppState props Action
layoutSpec :: Spec AppState {} Action
layoutSpec =
fold
[ routingSpec
......@@ -40,18 +40,19 @@ layoutSpec =
]
]
where
container :: Spec AppState props Action -> Spec AppState props Action
-- NP: what is it for ?
container :: Spec AppState {} Action -> Spec AppState {} Action
container = over _render \render d p s c ->
(render d p s c)
pagesComponent :: forall props. AppState -> Spec AppState props Action
pagesComponent :: AppState -> Spec AppState {} Action
pagesComponent s =
case s.currentRoute of
Just route -> selectSpec route
Nothing -> selectSpec Home
where
selectSpec :: Routes -> Spec AppState props Action
selectSpec :: Routes -> Spec AppState {} Action
selectSpec CorpusAnalysis = layout0 $ focus _corpusState _corpusAction CA.spec'
selectSpec Login = focus _loginState _loginAction LN.renderSpec
selectSpec Home = layout0 $ focus _landingState _LandingA (L.layoutLanding EN)
......@@ -68,11 +69,11 @@ pagesComponent s =
-- selectSpec _ = simpleSpec defaultPerformAction defaultRender
routingSpec :: forall props. Spec AppState props Action
routingSpec :: Spec AppState {} Action
routingSpec = simpleSpec performAction defaultRender
layout0 :: forall props. Spec AppState props Action
-> Spec AppState props Action
layout0 :: Spec AppState {} Action
-> Spec AppState {} Action
layout0 layout =
fold
[ layoutSidebar divSearchBar
......@@ -81,7 +82,7 @@ layout0 layout =
]
where
outerLayout1 = simpleSpec defaultPerformAction defaultRender
outerLayout :: Spec AppState props Action
outerLayout :: Spec AppState {} Action
outerLayout =
cont $ fold
[ withState \st ->
......@@ -97,8 +98,8 @@ layout0 layout =
bs = innerLayout $ layout
innerLayout :: Spec AppState props Action
-> Spec AppState props Action
innerLayout :: Spec AppState {} Action
-> Spec AppState {} Action
innerLayout = over _render \render d p s c ->
[ div [_id "page-wrapper"]
[
......@@ -106,8 +107,8 @@ layout0 layout =
]
]
layoutSidebar :: forall props. Spec AppState props Action
-> Spec AppState props Action
layoutSidebar :: Spec AppState {} Action
-> Spec AppState {} Action
layoutSidebar = over _render \render d p s c ->
[ div [ _id "dafixedtop"
, className "navbar navbar-inverse navbar-fixed-top"
......@@ -241,10 +242,10 @@ liNav (LiNav { title : title'
]
-- TODO put the search form in the center of the navBar
divSearchBar :: forall props. Spec AppState props Action
divSearchBar :: Spec AppState {} Action
divSearchBar = simpleSpec performAction render
where
render :: Render AppState props Action
render :: Render AppState {} Action
render dispatch _ state _ = [div [ className "" ] [ searchbar']]
where
searchbar' = ul [ className "nav navbar-nav col-md-6 col-md-offset-3"
......@@ -262,7 +263,7 @@ divSearchBar = simpleSpec performAction render
]
]
--divDropdownRight :: Render AppState props Action
--divDropdownRight :: Render AppState {} Action
divDropdownRight :: (Action -> Effect Unit) -> ReactElement
divDropdownRight d =
ul [className "nav navbar-nav pull-right"]
......@@ -285,10 +286,10 @@ divDropdownRight d =
]
]
layoutFooter :: forall props. Spec AppState props Action
layoutFooter :: Spec AppState {} Action
layoutFooter = simpleSpec performAction render
where
render :: Render AppState props Action
render :: Render AppState {} Action
render dispatch _ state _ = [div [ className "container1" ] [ hr', footerLegalInfo']]
where
footerLegalInfo' = footer [] [ p [] [ text "Gargantext "
......
......@@ -27,7 +27,7 @@ data Action
| LoadDatabaseDetails
| GO
performAction :: forall props. PerformAction State props Action
performAction :: PerformAction State {} Action
performAction NoOp _ _ = void do
modifyState identity
......
......@@ -21,7 +21,7 @@ import React.DOM.Props (_data, _id, _type, aria, className, onClick, role)
import Thermite (PerformAction, Render, Spec, _render, cotransform, modifyState, simpleSpec)
modalSpec :: forall props. Boolean -> String -> Spec State props Action -> Spec State props Action
modalSpec :: Boolean -> String -> Spec State {} Action -> Spec State {} Action
modalSpec sm t = over _render \render d p s c ->
[ div [ _id "addCorpus", className $ "modal myModal" <> if sm then "" else " fade"
, role "dialog"
......@@ -43,7 +43,7 @@ modalSpec sm t = over _render \render d p s c ->
]
spec' :: forall props. Spec State props Action
spec' :: Spec State {} Action
spec' = modalSpec true "Search Results" layoutAddcorpus
......@@ -93,10 +93,10 @@ layoutModal state =
]
layoutAddcorpus :: forall props. Spec State props Action
layoutAddcorpus :: Spec State {} Action
layoutAddcorpus = simpleSpec performAction render
where
render :: Render State props Action
render :: Render State {} Action
render dispatch _ state _ =
[ div [className "container1"] []
, div [className "container1"]
......
......@@ -28,7 +28,7 @@ data Action
| SetQuery String
performAction :: forall props. PerformAction State props Action
performAction :: PerformAction State {} Action
performAction NoOp _ _ = void do
modifyState identity
......@@ -45,10 +45,10 @@ performAction GO _ _ = void do
unsafeEventValue :: forall event. event -> String
unsafeEventValue e = (unsafeCoerce e).target.value
searchSpec :: forall props. Spec State props Action
searchSpec :: Spec State {} Action
searchSpec = simpleSpec performAction render
where
render :: Render State props Action
render :: Render State {} Action
render dispatch _ state _ =
[ div [className "container1"] []
, div [className "container1"]
......
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