Skip to content
GitLab
Explore
Sign in
Register
Primary navigation
Search or go to…
Project
P
Purescript Gargantext
Manage
Activity
Members
Labels
Plan
Issues
Issue boards
Milestones
Iterations
Wiki
Requirements
Code
Merge requests
Repository
Branches
Commits
Tags
Repository graph
Compare revisions
Snippets
Locked files
Build
Pipelines
Jobs
Pipeline schedules
Test cases
Artifacts
Deploy
Releases
Package Registry
Container Registry
Model registry
Operate
Environments
Terraform modules
Monitor
Incidents
Analyze
Value stream analytics
Contributor analytics
CI/CD analytics
Repository analytics
Code review analytics
Issue analytics
Insights
Model experiments
Help
Help
Support
GitLab documentation
Compare GitLab plans
Community forum
Contribute to GitLab
Provide feedback
Terms and privacy
Keyboard shortcuts
?
Snippets
Groups
Projects
Show more breadcrumbs
gargantext
Purescript Gargantext
Commits
8091879e
Commit
8091879e
authored
7 years ago
by
Abinaya Sudhir
Browse files
Options
Downloads
Patches
Plain Diff
Ngrams table design is done
parent
33234498
No related branches found
No related tags found
No related merge requests found
Changes
3
Hide whitespace changes
Inline
Side-by-side
Showing
3 changed files
dist/index.html
+1
-1
1 addition, 1 deletion
dist/index.html
src/Navigation.purs
+2
-2
2 additions, 2 deletions
src/Navigation.purs
src/NgramsTable.purs
+250
-18
250 additions, 18 deletions
src/NgramsTable.purs
with
253 additions
and
21 deletions
dist/index.html
+
1
−
1
View file @
8091879e
...
...
@@ -55,7 +55,7 @@
</style>
</head>
<body>
<div
id=
"app"
class =
"container"
></div>
<div
id=
"app"
class =
"container
-fluid
"
></div>
<script
src=
"bundle.js"
></script>
<script
src=
"js/bootstrap-native.min.js"
></script>
</body>
...
...
This diff is collapsed.
Click to expand it.
src/Navigation.purs
+
2
−
2
View file @
8091879e
...
...
@@ -311,9 +311,9 @@ layout0 layout =
else outerLayout1
, rs bs ]
ls = over _render \render d p s c ->
[div [className "col-md-
3
"] (render d p s c)]
[div [className "col-md-
2
"] (render d p s c)]
rs = over _render \render d p s c ->
[ div [className "col-md-
8
"] (render d p s c) ]
[ div [className "col-md-
10
"] (render d p s c) ]
cont = over _render \render d p s c ->
[ div [ className "row" ] (render d p s c) ]
...
...
This diff is collapsed.
Click to expand it.
src/NgramsTable.purs
+
250
−
18
View file @
8091879e
...
...
@@ -3,29 +3,47 @@ module NgramsTable where
import CSS.TextAlign (center, textAlign)
import Control.Monad.Eff.Console (CONSOLE)
import DOM (DOM)
import Data.Array (fold, toUnfoldable)
import Data.Array (
filter,
fold, toUnfoldable)
import Data.Either (Either(..))
import Data.Lens (Lens', Prism', lens, over, prism)
import Data.List (List
(..)
)
import Data.List (List)
import Data.Tuple (Tuple(..), uncurry)
import Network.HTTP.Affjax (AJAX)
import NgramsItem as NI
import Prelude hiding (div)
import Prelude (class Eq, class Ord, class Show, Unit, bind, map, not, pure, show, void, ($), (*), (+), (-), (/), (<), (<$>), (<>), (==), (>), (>=), (>>=))
import React (ReactElement)
import React.DOM hiding (style)
import React.DOM.Props (_id, className,
scope, styl
e)
import Thermite (PerformAction, Spec, _render, focus, foreach, modifyState, withState)
import React.DOM.Props (_id,
_type,
className,
href, name, onChange, onClick, onInput, placeholder, scope, selected, style, valu
e)
import Thermite (PerformAction, Spec, _render,
cotransform,
focus, foreach, modifyState, withState)
import Unsafe.Coerce (unsafeCoerce)
newtype State = State
{ items :: List NI.State
, search :: String
, selectString :: String
, totalPages :: Int
, currentPage :: Int
, pageSize :: PageSizes
, totalRecords :: Int
}
initialState :: State
initialState = State { items : toUnfoldable [NI.initialState]}
initialState = State { items : toUnfoldable [NI.initialState]
, search : ""
, selectString : ""
,totalPages : 10
, currentPage : 1
, pageSize : PS10
, totalRecords : 100
}
data Action
= NoOp
| ItemAction Int NI.Action
| ChangeString String
| SetInput String
| ChangePageSize PageSizes
| ChangePage Int
_itemsList :: Lens' State (List NI.State)
_itemsList = lens (\(State s) -> s.items) (\(State s) v -> State s { items = v })
...
...
@@ -38,13 +56,27 @@ _ItemAction = prism (uncurry ItemAction) \ta ->
performAction :: forall eff props. PerformAction ( console :: CONSOLE , ajax :: AJAX, dom :: DOM | eff ) State props Action
performAction _ _ _ = void do
modifyState id
modifyState \(State state) -> State $ state
performAction (ChangePageSize ps) _ _ = void (cotransform (\state -> changePageSize ps state ))
performAction (ChangePage p) _ _ = void do
modifyState \(State state) -> State $ state {currentPage = p}
performAction (ChangeString c) _ _ = void do
modifyState \(State state) -> State $ state { selectString = c }
performAction (SetInput s) _ _ = void do
modifyState \(State state) -> State $ state { search = s }
tableSpec :: forall eff props .Spec eff State props Action -> Spec eff State props Action
tableSpec = over _render \render dispatch p
s
c ->
[div [className "container
1
"]
tableSpec = over _render \render dispatch p
(State s)
c ->
[div [className "container
-fluid
"]
[
div [className "jumbotron"]
div [className "jumbotron
1
"]
[ div [className "row"]
[ div [className "panel panel-default"]
[
...
...
@@ -53,18 +85,53 @@ tableSpec = over _render \render dispatch p s c ->
[ span [className "glyphicon glyphicon-hand-down"] []
, text "Extracted Terms"
]
, div [className "savediv pull-left", style { margin :"1.5em 0 0 0", padding :"0 1em 0 0"}]
, div [className "row"]
[
div [className "savediv pull-left col-md-2", style { marginTop :"1.5em"}]
[ span [className "needsaveicon glyphicon glyphicon-import"] []
, button [_id "ImportListOrSaveAll", className "btn btn-warning", style {fontSize : "120%"}]
[ text "Import a Termlist"
]
]
, div []
[
,div [className "col-md-4", style {marginTop : "37px"}]
[ input [className "form-control "
, _id "id_password"
, name "search", placeholder "Search"
, _type "value"
,value s.search
,onInput \e -> dispatch (SetInput (unsafeEventValue e))
] []
]
, div [_id "filter_terms", className "col-md-6", style{ marginTop : "2.1em",paddingLeft :"1em"}]
[ div [className "row", style {marginTop : "6px"}]
[ div [className "col-md-3"]
[ select [_id "picklistmenu"
,className "form-control custom-select"
,onChange (\e -> dispatch (ChangeString $ (unsafeCoerce e).target.value))
] $ map optps1 aryPSMap
]
, div [className "col-md-3"]
[ select [_id "picktermtype",className "form-control custom-select",style {marginLeft : "1em"},onChange (\e -> dispatch (ChangeString $ (unsafeCoerce e).target.value)) ] $ map optps1 aryPS1
]
,div [className "col-md-3"]
[ sizeDD s.pageSize dispatch
]
]
]
]
, table [ className "table able table-bordered"]
, div [className "col-md-6", style {marginTop : "24px", marginBottom : "14px"}]
[ textDescription s.currentPage s.pageSize s.totalRecords
, pagination dispatch s.totalPages s.currentPage
]
]
]
, div [_id "terms_table", className "panel-body"] [table [ className "table able table-bordered"]
[ thead [ className "tableHeader table-bordered"]
[ tr []
[ th [ scope "col"] [ text "Map" ]
...
...
@@ -73,13 +140,15 @@ tableSpec = over _render \render dispatch p s c ->
, th [ scope "col"] [ text "Occurences (nb)" ]
]
]
, tbody [] $ render dispatch p
s
c
, tbody [] $ render dispatch p
(State s)
c
]
]
]
]
]
]
]
ngramsTableSpec :: forall props eff . Spec (console::CONSOLE, ajax::AJAX, dom::DOM | eff) State props Action
ngramsTableSpec = container $ fold
[ tableSpec $ withState \st ->
...
...
@@ -89,6 +158,169 @@ ngramsTableSpec = container $ fold
container :: forall eff state props action. Spec eff state props action -> Spec eff state props action
container = over _render \render d p s c ->
[ div [ className "container" ] $
[ div [ className "container
-fluid
" ] $
(render d p s c)
]
aryPSMap :: Array String
aryPSMap = ["All terms", "Map terms", "Stop terms", "Other terms"]
aryPS1 :: Array String
aryPS1 = ["All types","One-word terms", "Multi-word terms"]
optps1 :: String -> ReactElement
optps1 val = option [ value val ] [text val]
unsafeEventValue :: forall event. event -> String
unsafeEventValue e = (unsafeCoerce e).target.value
changePageSize :: PageSizes -> State -> State
changePageSize ps (State td) =
State $ td { pageSize = ps
, totalPages = td.totalRecords / pageSizes2Int ps
, currentPage = 1
}
data PageSizes = PS10 | PS20 | PS50 | PS100
derive instance eqPageSizes :: Eq PageSizes
instance showPageSize :: Show PageSizes where
show PS10 = "10"
show PS20 = "20"
show PS50 = "50"
show PS100 = "100"
pageSizes2Int :: PageSizes -> Int
pageSizes2Int PS10 = 10
pageSizes2Int PS20 = 20
pageSizes2Int PS50 = 50
pageSizes2Int PS100 = 100
aryPS :: Array PageSizes
aryPS = [PS10, PS20, PS50, PS100]
string2PageSize :: String -> PageSizes
string2PageSize "10" = PS10
string2PageSize "20" = PS20
string2PageSize "50" = PS50
string2PageSize "100" = PS100
string2PageSize _ = PS10
sizeDD :: PageSizes -> _ -> ReactElement
sizeDD ps d
= p []
[ text "Show : "
, select [onChange (\e -> d (ChangePageSize $ string2PageSize $ (unsafeCoerce e).target.value))] $ map (optps ps) aryPS
]
optps :: PageSizes -> PageSizes -> ReactElement
optps cv val = option [ selected (cv == val), value $ show val ] [text $ show val]
textDescription :: Int -> PageSizes -> Int -> ReactElement
textDescription currPage pageSize totalRecords
= div [className "row1"]
[ div [className "col-md-6"]
[ text $ "Showing " <> show start <> " to " <> show end <> " of " <> show totalRecords ]
]
where
start = (currPage - 1) * pageSizes2Int pageSize + 1
end' = currPage * pageSizes2Int pageSize
end = if end' > totalRecords then totalRecords else end'
pagination :: _ -> Int -> Int -> ReactElement
pagination d tp cp
= span [] $
[ text "Pages: "
, prev
, first
, ldots
]
<>
lnums
<>
[b' [text $ " " <> show cp <> " "]]
<>
rnums
<>
[ rdots
, last
, next
]
where
prev = if cp == 1 then
text " Previous "
else
span []
[ text " "
, a [ href "javascript:void()"
, onClick (\e -> d $ ChangePage $ cp - 1)
] [text "Previous"]
, text " "
]
next = if cp == tp then
text " Next "
else
span []
[ text " "
, a [ href "javascript:void()"
, onClick (\e -> d $ ChangePage $ cp + 1)
] [text "Next"]
, text " "
]
first = if cp == 1 then
text ""
else
span []
[ text " "
, a [ href "javascript:void()"
, onClick (\e -> d $ ChangePage 1)
] [text "1"]
, text " "
]
last = if cp == tp then
text ""
else
span []
[ text " "
, a [ href "javascript:void()"
, onClick (\e -> d $ ChangePage tp)
] [text $ show tp]
, text " "
]
ldots = if cp >= 5 then
text " ... "
else
text ""
rdots = if cp + 3 < tp then
text " ... "
else
text ""
lnums = map (\i -> fnmid d i) $ filter (lessthan 1) [cp - 2, cp - 1]
rnums = map (\i -> fnmid d i) $ filter (greaterthan tp) [cp + 1, cp + 2]
fnmid :: _ -> Int -> ReactElement
fnmid d i
= span []
[ text " "
, a [ href "javascript:void()"
, onClick (\e -> d $ ChangePage i)
] [text $ show i]
, text " "
]
lessthan :: forall t28. Ord t28 => t28 -> t28 -> Boolean
lessthan x y = x < y
greaterthan :: forall t28. Ord t28 => t28 -> t28 -> Boolean
greaterthan x y = x > y
This diff is collapsed.
Click to expand it.
Preview
0%
Loading
Try again
or
attach a new file
.
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Save comment
Cancel
Please
register
or
sign in
to comment