Commit d5879c32 authored by Abinaya Sudhir's avatar Abinaya Sudhir

Annotation Document view done

parent 3b021b7f
...@@ -21,7 +21,7 @@ ...@@ -21,7 +21,7 @@
} }
#page-wrapper { #page-wrapper {
margin-top : 56px; margin-top : 96px;
} }
#user-page-header { #user-page-header {
......
...@@ -2,22 +2,29 @@ module AnnotationDocumentView where ...@@ -2,22 +2,29 @@ module AnnotationDocumentView where
import Prelude hiding (div) import Prelude hiding (div)
import React (ReactElement) import React (ReactElement)
import React.DOM (a, button, div, h4, 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, onChange, role, selected, value) import React.DOM.Props (_data, _id, _type, aria, className, href, name, onChange, onInput, placeholder, role, selected, style, value)
import Thermite (PerformAction, Render, Spec, cotransform, modifyState, simpleSpec) import Thermite (PerformAction, Render, Spec, cotransform, modifyState, simpleSpec)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
type State = String type State =
{
inputValue :: String
}
initialState :: State initialState :: State
initialState = "" initialState =
{
inputValue : ""
}
data Action data Action
= NoOp = NoOp
| ChangeString String | ChangeString String
| ChangeAnotherString String | ChangeAnotherString String
| SetInput String
performAction :: PerformAction _ State _ Action performAction :: PerformAction _ State _ Action
...@@ -27,6 +34,8 @@ performAction (ChangeString ps) _ _ = pure unit ...@@ -27,6 +34,8 @@ performAction (ChangeString ps) _ _ = pure unit
performAction (ChangeAnotherString ps) _ _ = pure unit performAction (ChangeAnotherString ps) _ _ = pure unit
performAction (SetInput ps) _ _ = pure unit
docview :: Spec _ State _ Action docview :: Spec _ State _ Action
...@@ -34,16 +43,21 @@ docview = simpleSpec performAction render ...@@ -34,16 +43,21 @@ docview = simpleSpec performAction render
where where
render :: Render State _ Action render :: Render State _ Action
render dispatch _ state _ = render dispatch _ state _ =
[ div [className "container"]
[ div [className "row"]
[ div [className "col-md-4"]
[ div [className "row"]
[ div [className "col-md-12 form-control"] [select [onChange (\e -> dispatch (ChangeString $ (unsafeCoerce e).target.value)) ] $ map optps aryPS ]
, div [className "col-md-12 form-control"] [ select [onChange (\e -> dispatch (ChangeAnotherString $ (unsafeCoerce e).target.value)) ] $ map optps aryPS1 ]
]
, div [className "row"]
[ [
nav [] div [className "container"]
[
div [className "row"]
[
div [className "col-md-4", style {border : "1px solid black", padding : "34px"}]
[
div [className "row"]
[
div [className "col-md-12 input-group mb-3"] [select [className "form-control custom-select",onChange (\e -> dispatch (ChangeString $ (unsafeCoerce e).target.value)) ] $ map optps aryPS ]
, div [className "col-md-12 form-control input-group mb-3"] [ select [className "form-control custom-select",onChange (\e -> dispatch (ChangeAnotherString $ (unsafeCoerce e).target.value)) ] $ map optps aryPS1 ]
]
, div [className "row", style { marginTop : "35px"}]
[
nav [ ]
[ div [className "nav nav-tabs", _id "nav-tab",role "tablist"] [ 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 "Publications (12)"] [ 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 "Publications (12)"]
, 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 "Brevets (2)"] , 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 "Brevets (2)"]
...@@ -59,7 +73,11 @@ docview = simpleSpec performAction render ...@@ -59,7 +73,11 @@ docview = simpleSpec performAction render
, _id "nav-home" , _id "nav-home"
] ]
[ [
input [] [] h6 [] [text "Add a free term to STOPLIST"]
, 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))] []
, 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"]
] ]
...@@ -115,23 +133,5 @@ aryPS1 = ["Nothing Selected","STOPLIST", "MAINLIST", "MAPLIST"] ...@@ -115,23 +133,5 @@ aryPS1 = ["Nothing Selected","STOPLIST", "MAINLIST", "MAPLIST"]
optps :: String -> ReactElement optps :: String -> ReactElement
optps val = option [ value val ] [text val] optps val = option [ value val ] [text val]
unsafeEventValue :: forall event. event -> String
unsafeEventValue e = (unsafeCoerce e).target.value
-- ul [className "nav nav-pills mb-3", _id "pills-tab",role "tablist"]
-- [ li [className "nav-item"]
-- [ a [className "nav-link active", _id "pills-stop", _data {toggle : "pill"}, href "#pills-stop", role "tab", aria {controls :"pills-stop"}, aria {selected : true}] []
-- ]
-- , li [className "nav-item"]
-- [ a [className "nav-link", _id "pills-main", _data {toggle : "pill"}, href "#pills-main", role "tab", aria {controls :"pills-main"}, aria {selected : false}] []
-- ]
-- , li [className "nav-item"]
-- [ a [className "nav-link", _id "pills-map", _data {toggle : "pill"}, href "#pills-map", role "tab", aria {controls :"pills-map"}, aria {selected : false}] []
-- ]
-- ]
-- , div [className "tab-content", _id "pills-tabContent"]
-- [ div [className "tab-pane fade show active", _id "pills-stop", role "tabpanel" ,aria {labelledby : "pills-stop-tab"}] []
-- , div [ className "tab-pane fade", _id "pills-main", role "tabpanel" ,aria {labelledby : "pills-main-tab"}] []
-- , div [ className "tab-pane fade", _id "pills-map", role "tabpanel" ,aria {labelledby : "pills-map-tab"}] []
-- ]
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