Commit 1523b6dd authored by Abinaya Sudhir's avatar Abinaya Sudhir

Tabview fixed

parent 24eaa34e
...@@ -3,31 +3,23 @@ module Authorview where ...@@ -3,31 +3,23 @@ module Authorview where
import Control.Monad.Eff.Console (CONSOLE) import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM) import DOM (DOM)
import Data.Array (fold)
import DocView as D
import Network.HTTP.Affjax (AJAX) import Network.HTTP.Affjax (AJAX)
import Prelude hiding (div) import Prelude hiding (div)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec) import React.DOM (h3, text)
import Thermite (PerformAction, Render, Spec, defaultPerformAction, modifyState, simpleSpec)
type State = String type State = D.State
initialState :: State initialState :: State
initialState = "" initialState = D.tdata
data Action = NoOp
performAction :: forall eff props. PerformAction ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
performAction NoOp _ _ = void do
modifyState id
type Action = D.Action
authorSpec :: forall props eff . Spec ( console :: CONSOLE authorSpec :: forall props eff . Spec ( console :: CONSOLE
...@@ -35,8 +27,11 @@ authorSpec :: forall props eff . Spec ( console :: CONSOLE ...@@ -35,8 +27,11 @@ authorSpec :: forall props eff . Spec ( console :: CONSOLE
, dom :: DOM , dom :: DOM
| eff | eff
) State props Action ) State props Action
authorSpec = simpleSpec performAction render authorSpec = simpleSpec defaultPerformAction render
where where
render :: Render State props Action render :: Render State props Action
render dispatch _ state _ = render dispatch _ state _ =
[] [ h3 [] [text "AuthorView"]]
authorspec' :: forall eff props. Spec (dom :: DOM, console :: CONSOLE, ajax :: AJAX | eff) State props Action
authorspec' = fold [authorSpec, D.layoutDocview]
...@@ -106,26 +106,7 @@ layoutDocview = simpleSpec performAction render ...@@ -106,26 +106,7 @@ layoutDocview = simpleSpec performAction render
[ div [className "row"] [ div [className "row"]
[ [
div [className "col-md-12"] div [className "col-md-12"]
[ -- nav [] [ p''
-- [ div [className "nav nav-tabs", _id "nav-tab",role "tablist"]
-- [
-- a [ className "nav-item nav-link active"
-- , _id "nav-home-tab"
-- , _data {toggle : "tab"}
-- , href "#nav-home"
-- , role "tab"
-- , aria {controls : "nav-home"}
-- , aria {selected:true}] [ text "Documents"]
-- , a [className "nav-item nav-link",_id "nav-profile-tab", _data {toggle : "tab"},href "#nav-profile",role "tab",aria {controls : "nav-profile"},aria {selected:true}] [ text "Sources"]
-- ,a [className "nav-item nav-link",_id "nav-contact-tab", _data {toggle : "tab"},href "#nav-contact",role "tab",aria {controls : "nav-contact"},aria {selected:true}] [ text "Authors"]
-- ,a [className "nav-item nav-link",_id "nav-contact-tab", _data {toggle : "tab"},href "#nav-contact",role "tab",aria {controls : "nav-contact"},aria {selected:true}] [ text "Terms"]
-- ,a [className "nav-item nav-link",_id "nav-contact-tab", _data {toggle : "tab"},href "#nav-contact",role "tab",aria {controls : "nav-contact"},aria {selected:true}] [ text "(+)"]
-- ]
-- ]
p''
, h3 [] [text "Chart Title"] , h3 [] [text "Chart Title"]
, histogram , histogram
, p'' , p''
...@@ -175,9 +156,6 @@ performAction LoadData _ _ = void do ...@@ -175,9 +156,6 @@ performAction LoadData _ _ = void do
} }
-- performAction (ToggleFolder i) _ _ = void (cotransform (\(TableData td) -> TableData $ td {tree = toggleNode i td.tree}))
changePageSize :: PageSizes -> CorpusTableData -> CorpusTableData changePageSize :: PageSizes -> CorpusTableData -> CorpusTableData
changePageSize ps (TableData td) = changePageSize ps (TableData td) =
TableData $ td { pageSize = ps TableData $ td { pageSize = ps
......
...@@ -3,30 +3,20 @@ module Sourceview where ...@@ -3,30 +3,20 @@ module Sourceview where
import Control.Monad.Eff.Console (CONSOLE) import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM) import DOM (DOM)
import Data.Array (fold)
import DocView as D
import Network.HTTP.Affjax (AJAX) import Network.HTTP.Affjax (AJAX)
import Prelude hiding (div) import Prelude hiding (div)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec) import React.DOM (h3, text)
import Thermite (PerformAction, Render, Spec, defaultPerformAction, modifyState, simpleSpec)
type State = D.State
type State = String
initialState :: State
initialState = ""
data Action = NoOp
performAction :: forall eff props. PerformAction ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
performAction NoOp _ _ = void do
modifyState id
initialState :: D.State
initialState = D.tdata
type Action = D.Action
sourceSpec :: forall props eff . Spec ( console :: CONSOLE sourceSpec :: forall props eff . Spec ( console :: CONSOLE
...@@ -34,8 +24,11 @@ sourceSpec :: forall props eff . Spec ( console :: CONSOLE ...@@ -34,8 +24,11 @@ sourceSpec :: forall props eff . Spec ( console :: CONSOLE
, dom :: DOM , dom :: DOM
| eff | eff
) State props Action ) State props Action
sourceSpec = simpleSpec performAction render sourceSpec = simpleSpec defaultPerformAction render
where where
render :: Render State props Action render :: Render State props Action
render dispatch _ state _ = render dispatch _ state _ =
[] [ h3 [] [text "Source view"]]
sourcespec' :: forall eff props. Spec (dom :: DOM, console :: CONSOLE, ajax :: AJAX | eff) State props Action
sourcespec' = fold [sourceSpec, D.layoutDocview]
...@@ -70,7 +70,7 @@ _authorAction = prism AuthorviewA \ action -> ...@@ -70,7 +70,7 @@ _authorAction = prism AuthorviewA \ action ->
_-> Left action _-> Left action
authorPageSpec :: forall eff props. Spec (dom :: DOM, console::CONSOLE, ajax :: AJAX | eff) State props Action authorPageSpec :: forall eff props. Spec (dom :: DOM, console::CONSOLE, ajax :: AJAX | eff) State props Action
authorPageSpec = focus _authorlens _authorAction AV.authorSpec authorPageSpec = focus _authorlens _authorAction AV.authorspec'
_sourcelens :: Lens' State SV.State _sourcelens :: Lens' State SV.State
...@@ -85,7 +85,7 @@ _sourceAction = prism SourceviewA \ action -> ...@@ -85,7 +85,7 @@ _sourceAction = prism SourceviewA \ action ->
sourcePageSpec :: forall eff props. Spec (dom :: DOM, console :: CONSOLE, ajax :: AJAX | eff) State props Action sourcePageSpec :: forall eff props. Spec (dom :: DOM, console :: CONSOLE, ajax :: AJAX | eff) State props Action
sourcePageSpec = focus _sourcelens _sourceAction SV.sourceSpec sourcePageSpec = focus _sourcelens _sourceAction SV.sourcespec'
_termslens :: Lens' State TV.State _termslens :: Lens' State TV.State
...@@ -100,7 +100,7 @@ _termsAction = prism TermsviewA \ action -> ...@@ -100,7 +100,7 @@ _termsAction = prism TermsviewA \ action ->
termsPageSpec :: forall eff props. Spec (dom :: DOM, console :: CONSOLE, ajax :: AJAX | eff) State props Action termsPageSpec :: forall eff props. Spec (dom :: DOM, console :: CONSOLE, ajax :: AJAX | eff) State props Action
termsPageSpec = focus _termslens _termsAction TV.termsSpec termsPageSpec = focus _termslens _termsAction TV.termSpec'
_tablens :: Lens' State Tab.State _tablens :: Lens' State Tab.State
......
...@@ -4,31 +4,22 @@ module Termsview where ...@@ -4,31 +4,22 @@ module Termsview where
import Control.Monad.Eff.Console (CONSOLE) import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM) import DOM (DOM)
import Data.Array (fold)
import DocView as D
import Network.HTTP.Affjax (AJAX) import Network.HTTP.Affjax (AJAX)
import Prelude hiding (div) import Prelude hiding (div)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec) import React.DOM (h3, text)
import Thermite (PerformAction, Render, Spec, defaultPerformAction, modifyState, simpleSpec)
type State = D.State
type State = String
initialState :: State
initialState = ""
data Action = NoOp
performAction :: forall eff props. PerformAction ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
performAction NoOp _ _ = void do
modifyState id
initialState :: D.State
initialState = D.tdata
type Action = D.Action
termsSpec :: forall props eff . Spec ( console :: CONSOLE termsSpec :: forall props eff . Spec ( console :: CONSOLE
...@@ -36,8 +27,11 @@ termsSpec :: forall props eff . Spec ( console :: CONSOLE ...@@ -36,8 +27,11 @@ termsSpec :: forall props eff . Spec ( console :: CONSOLE
, dom :: DOM , dom :: DOM
| eff | eff
) State props Action ) State props Action
termsSpec = simpleSpec performAction render termsSpec = simpleSpec defaultPerformAction render
where where
render :: Render State props Action render :: Render State props Action
render dispatch _ state _ = render dispatch _ state _ =
[] [ h3 [] [text "Terms view"]]
termSpec' :: forall eff props. Spec (dom :: DOM, console :: CONSOLE, ajax :: AJAX | eff) State props Action
termSpec' = fold [termsSpec, D.layoutDocview]
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