Commit ad3df19b authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski Committed by Alexandre Delanoë

[ngrams] fix select all checkbox

parent fbe8ac8a
...@@ -16,6 +16,7 @@ import Data.Map (Map) ...@@ -16,6 +16,7 @@ import Data.Map (Map)
import Data.Map as Map import Data.Map as Map
import Data.Maybe (Maybe(..), maybe, isJust, isNothing) import Data.Maybe (Maybe(..), maybe, isJust, isNothing)
import Data.Monoid.Additive (Additive(..)) import Data.Monoid.Additive (Additive(..))
import Data.Nullable (Nullable, toMaybe, null)
import Data.Ord.Down (Down(..)) import Data.Ord.Down (Down(..))
import Data.Set (Set) import Data.Set (Set)
import Data.Set as Set import Data.Set as Set
...@@ -53,16 +54,11 @@ type State' = ...@@ -53,16 +54,11 @@ type State' =
-- be removed. -- be removed.
, ngramsSelection :: Set NgramsTerm , ngramsSelection :: Set NgramsTerm
-- ^ The set of selected checkboxes of the first column. -- ^ The set of selected checkboxes of the first column.
, ngramsSelectAll :: Boolean
-- ^ The checkbox to select all the checkboxes of the first column.
) )
_ngramsChildren :: forall row. Lens' { ngramsChildren :: Map NgramsTerm Boolean | row } (Map NgramsTerm Boolean) _ngramsChildren :: forall row. Lens' { ngramsChildren :: Map NgramsTerm Boolean | row } (Map NgramsTerm Boolean)
_ngramsChildren = prop (SProxy :: SProxy "ngramsChildren") _ngramsChildren = prop (SProxy :: SProxy "ngramsChildren")
_ngramsSelectAll :: forall row. Lens' { ngramsSelectAll :: Boolean | row } Boolean
_ngramsSelectAll = prop (SProxy :: SProxy "ngramsSelectAll")
_ngramsSelection :: forall row. Lens' { ngramsSelection :: Set NgramsTerm | row } (Set NgramsTerm) _ngramsSelection :: forall row. Lens' { ngramsSelection :: Set NgramsTerm | row } (Set NgramsTerm)
_ngramsSelection = prop (SProxy :: SProxy "ngramsSelection") _ngramsSelection = prop (SProxy :: SProxy "ngramsSelection")
...@@ -74,7 +70,6 @@ initialState' (Versioned {version}) = ...@@ -74,7 +70,6 @@ initialState' (Versioned {version}) =
, ngramsVersion: version , ngramsVersion: version
, ngramsParent: Nothing , ngramsParent: Nothing
, ngramsChildren: mempty , ngramsChildren: mempty
, ngramsSelectAll: false
, ngramsSelection: mempty , ngramsSelection: mempty
} }
...@@ -88,8 +83,6 @@ type State = ...@@ -88,8 +83,6 @@ type State =
-- be removed. -- be removed.
, ngramsSelection :: Set NgramsTerm , ngramsSelection :: Set NgramsTerm
-- ^ The set of selected checkboxes of the first column. -- ^ The set of selected checkboxes of the first column.
, ngramsSelectAll :: Boolean
-- ^ The checkbox to select all the checkboxes of the first column.
) )
initialState :: VersionedNgramsTable -> State initialState :: VersionedNgramsTable -> State
...@@ -100,7 +93,6 @@ initialState (Versioned {version}) = { ...@@ -100,7 +93,6 @@ initialState (Versioned {version}) = {
, ngramsVersion: version , ngramsVersion: version
, ngramsParent: Nothing , ngramsParent: Nothing
, ngramsChildren: mempty , ngramsChildren: mempty
, ngramsSelectAll: false
, ngramsSelection: mempty , ngramsSelection: mempty
} }
...@@ -143,12 +135,12 @@ addNewNgramA :: NgramsTerm -> Action ...@@ -143,12 +135,12 @@ addNewNgramA :: NgramsTerm -> Action
addNewNgramA ngram = CommitPatch $ addNewNgram ngram CandidateTerm addNewNgramA ngram = CommitPatch $ addNewNgram ngram CandidateTerm
type Dispatch = Action -> Effect Unit type Dispatch = Action -> Effect Unit
type PreConversionRows = L.List (Tuple NgramsTerm NgramsElement)
type TableContainerProps = type TableContainerProps =
( dispatch :: Dispatch ( dispatch :: Dispatch
, ngramsChildren :: Map NgramsTerm Boolean , ngramsChildren :: Map NgramsTerm Boolean
, ngramsParent :: Maybe NgramsTerm , ngramsParent :: Maybe NgramsTerm
, ngramsSelectAll :: Boolean
, ngramsSelection :: Set NgramsTerm , ngramsSelection :: Set NgramsTerm
, ngramsTable :: NgramsTable , ngramsTable :: NgramsTable
, path :: R.State PageParams , path :: R.State PageParams
...@@ -162,7 +154,6 @@ tableContainerCpt :: Record TableContainerProps -> R.Component T.TableContainerP ...@@ -162,7 +154,6 @@ tableContainerCpt :: Record TableContainerProps -> R.Component T.TableContainerP
tableContainerCpt { dispatch tableContainerCpt { dispatch
, ngramsChildren , ngramsChildren
, ngramsParent , ngramsParent
, ngramsSelectAll
, ngramsSelection , ngramsSelection
, ngramsTable: ngramsTableCache , ngramsTable: ngramsTableCache
, path: {searchQuery, termListFilter, termSizeFilter} /\ setPath , path: {searchQuery, termListFilter, termSizeFilter} /\ setPath
...@@ -234,13 +225,13 @@ tableContainerCpt { dispatch ...@@ -234,13 +225,13 @@ tableContainerCpt { dispatch
, H.button {className: "btn btn-primary", on: {click: (const $ dispatch AddTermChildren)}} [H.text "Save"] , H.button {className: "btn btn-primary", on: {click: (const $ dispatch AddTermChildren)}} [H.text "Save"]
, H.button {className: "btn btn-secondary", on: {click: (const $ dispatch $ SetParentResetChildren Nothing)}} [H.text "Cancel"] , H.button {className: "btn btn-secondary", on: {click: (const $ dispatch $ SetParentResetChildren Nothing)}} [H.text "Cancel"]
]) ngramsParent) ]) ngramsParent)
, selectAllButtons ngramsSelectAll , selectButtons (selectionsExist ngramsSelection)
, H.div {id: "terms_table", className: "panel-body"} , H.div {id: "terms_table", className: "panel-body"}
[ H.table {className: "table able"} [ H.table {className: "table able"}
[ H.thead {className: "tableHeader"} [props.tableHead] [ H.thead {className: "tableHeader"} [props.tableHead]
, H.tbody {} props.tableBody] ] , H.tbody {} props.tableBody] ]
, selectAllButtons ngramsSelectAll , selectButtons (selectionsExist ngramsSelection)
] ]
] ]
] ]
...@@ -250,8 +241,11 @@ tableContainerCpt { dispatch ...@@ -250,8 +241,11 @@ tableContainerCpt { dispatch
setTermSizeFilter x = setPath $ _ { termSizeFilter = x } setTermSizeFilter x = setPath $ _ { termSizeFilter = x }
setSelection = dispatch <<< setTermListSetA ngramsTableCache ngramsSelection setSelection = dispatch <<< setTermListSetA ngramsTableCache ngramsSelection
selectAllButtons false = H.div {} [] selectionsExist :: Set NgramsTerm -> Boolean
selectAllButtons true = selectionsExist = not <<< Set.isEmpty
selectButtons false = H.div {} []
selectButtons true =
H.li {className: " list-group-item"} [ H.li {className: " list-group-item"} [
H.button { className: "btn btn-primary" H.button { className: "btn btn-primary"
, on: {click: const $ setSelection GraphTerm } , on: {click: const $ setSelection GraphTerm }
...@@ -339,7 +333,6 @@ loadedNgramsTableSpecCpt = R.hooksComponent "G.C.NT.loadedNgramsTable" cpt ...@@ -339,7 +333,6 @@ loadedNgramsTableSpecCpt = R.hooksComponent "G.C.NT.loadedNgramsTable" cpt
, state: (state@{ ngramsChildren , state: (state@{ ngramsChildren
, ngramsLocalPatch , ngramsLocalPatch
, ngramsParent , ngramsParent
, ngramsSelectAll
, ngramsSelection , ngramsSelection
, ngramsVersion } /\ setState) , ngramsVersion } /\ setState)
, tabNgramType , tabNgramType
...@@ -353,16 +346,18 @@ loadedNgramsTableSpecCpt = R.hooksComponent "G.C.NT.loadedNgramsTable" cpt ...@@ -353,16 +346,18 @@ loadedNgramsTableSpecCpt = R.hooksComponent "G.C.NT.loadedNgramsTable" cpt
, container: tableContainer { dispatch: performAction , container: tableContainer { dispatch: performAction
, ngramsChildren , ngramsChildren
, ngramsParent , ngramsParent
, ngramsSelectAll
, ngramsSelection , ngramsSelection
, ngramsTable , ngramsTable
, path , path
, tabNgramType , tabNgramType
} }
, params: params /\ setParams -- TODO-LENS , params: params /\ setParams -- TODO-LENS
, rows: filteredRows , rows: filteredConvertedRows
, totalRecords , totalRecords
, wrapColElts , wrapColElts: wrapColElts { allNgramsSelected
, dispatch: performAction
, ngramsSelection
}
} }
] ]
where where
...@@ -393,10 +388,11 @@ loadedNgramsTableSpecCpt = R.hooksComponent "G.C.NT.loadedNgramsTable" cpt ...@@ -393,10 +388,11 @@ loadedNgramsTableSpecCpt = R.hooksComponent "G.C.NT.loadedNgramsTable" cpt
performAction ToggleSelectAll = performAction ToggleSelectAll =
setState toggler setState toggler
where where
toggler s@{ ngramsSelectAll: true } = s { ngramsSelection = Set.empty :: Set NgramsTerm toggler s@{ ngramsSelection } =
, ngramsSelectAll = false } if allNgramsSelected then
toggler s = s { ngramsSelection = roots s { ngramsSelection = Set.empty :: Set NgramsTerm }
, ngramsSelectAll = true } else
s { ngramsSelection = selectNgramsOnFirstPage filteredRows }
performAction Synchronize = syncPatchesR path' (state /\ setState) performAction Synchronize = syncPatchesR path' (state /\ setState)
performAction (CommitPatch pt) = performAction (CommitPatch pt) =
commitPatchR (Versioned {version: ngramsVersion, data: pt}) (state /\ setState) commitPatchR (Versioned {version: ngramsVersion, data: pt}) (state /\ setState)
...@@ -415,8 +411,11 @@ loadedNgramsTableSpecCpt = R.hooksComponent "G.C.NT.loadedNgramsTable" cpt ...@@ -415,8 +411,11 @@ loadedNgramsTableSpecCpt = R.hooksComponent "G.C.NT.loadedNgramsTable" cpt
commitPatchR (Versioned {version: ngramsVersion, data: pt}) (state /\ setState) commitPatchR (Versioned {version: ngramsVersion, data: pt}) (state /\ setState)
totalRecords = L.length rows totalRecords = L.length rows
filteredRows = convertRow <$> T.filterRows { params } rows filteredConvertedRows :: T.Rows
rows :: L.List (Tuple NgramsTerm NgramsElement) filteredConvertedRows = convertRow <$> filteredRows
filteredRows :: PreConversionRows
filteredRows = T.filterRows { params } rows
rows :: PreConversionRows
rows = orderWith ( rows = orderWith (
addOccT <$> ( addOccT <$> (
L.filter rowsFilterT $ Map.toUnfoldable (ngramsTable ^. _NgramsTable) L.filter rowsFilterT $ Map.toUnfoldable (ngramsTable ^. _NgramsTable)
...@@ -447,6 +446,8 @@ loadedNgramsTableSpecCpt = R.hooksComponent "G.C.NT.loadedNgramsTable" cpt ...@@ -447,6 +446,8 @@ loadedNgramsTableSpecCpt = R.hooksComponent "G.C.NT.loadedNgramsTable" cpt
-- let Additive occurrences = sumOccurrences ngramsTable ngramsElement in -- let Additive occurrences = sumOccurrences ngramsTable ngramsElement in
-- Tuple ne (ngramsElement # _NgramsElement <<< _occurrences .~ occurrences) -- Tuple ne (ngramsElement # _NgramsElement <<< _occurrences .~ occurrences)
allNgramsSelected = allNgramsSelectedOnFirstPage ngramsSelection filteredRows
ngramsTable = applyNgramsPatches state initTable ngramsTable = applyNgramsPatches state initTable
roots = rootsOf ngramsTable roots = rootsOf ngramsTable
ngramsParentRoot :: Maybe NgramsTerm ngramsParentRoot :: Maybe NgramsTerm
...@@ -477,15 +478,10 @@ loadedNgramsTableSpecCpt = R.hooksComponent "G.C.NT.loadedNgramsTable" cpt ...@@ -477,15 +478,10 @@ loadedNgramsTableSpecCpt = R.hooksComponent "G.C.NT.loadedNgramsTable" cpt
_ -> identity -- the server ordering is enough here _ -> identity -- the server ordering is enough here
colNames = T.ColumnName <$> ["Select", "Map", "Stop", "Terms", "Score"] -- see convOrderBy colNames = T.ColumnName <$> ["Select", "Map", "Stop", "Terms", "Score"] -- see convOrderBy
selected =
H.input { checked: ngramsSelectAll
, className: "checkbox"
, on: { change: const $ performAction $ ToggleSelectAll }
, type: "checkbox" }
-- This is used to *decorate* the Select header with the checkbox. -- This is used to *decorate* the Select header with the checkbox.
wrapColElts (T.ColumnName "Select") = const [selected] wrapColElts scProps (T.ColumnName "Select") = const [selectionCheckbox scProps]
wrapColElts (T.ColumnName "Score") = (_ <> [H.text ("(" <> show scoreType <> ")")]) wrapColElts _ (T.ColumnName "Score") = (_ <> [H.text ("(" <> show scoreType <> ")")])
wrapColElts _ = identity wrapColElts _ _ = identity
setParams f = setPath $ \p@{params: ps} -> p {params = f ps} setParams f = setPath $ \p@{params: ps} -> p {params = f ps}
search :: R.Element search :: R.Element
...@@ -496,6 +492,48 @@ loadedNgramsTableSpecCpt = R.hooksComponent "G.C.NT.loadedNgramsTable" cpt ...@@ -496,6 +492,48 @@ loadedNgramsTableSpecCpt = R.hooksComponent "G.C.NT.loadedNgramsTable" cpt
setSearchQuery x = setPath $ _ { searchQuery = x } setSearchQuery x = setPath $ _ { searchQuery = x }
allNgramsSelectedOnFirstPage :: Set NgramsTerm -> PreConversionRows -> Boolean
allNgramsSelectedOnFirstPage selected rows = selected == (selectNgramsOnFirstPage rows)
selectNgramsOnFirstPage :: PreConversionRows -> Set NgramsTerm
selectNgramsOnFirstPage rows = Set.fromFoldable $ fst <$> rows
type SelectionCheckboxProps =
(
allNgramsSelected :: Boolean
, dispatch :: Dispatch
, ngramsSelection :: Set NgramsTerm
)
selectionCheckbox :: Record SelectionCheckboxProps -> R.Element
selectionCheckbox props = R.createElement selectionCheckboxCpt props []
selectionCheckboxCpt :: R.Component SelectionCheckboxProps
selectionCheckboxCpt = R.hooksComponent "G.C.NT.selectionCheckbox" cpt
where
cpt { allNgramsSelected, dispatch, ngramsSelection } _ = do
ref <- R.useRef null
R.useEffect' $ do
let mCb = toMaybe $ R.readRef ref
case mCb of
Nothing -> pure unit
Just cb -> do
log2 "[loadedNgramsTableSpec] ngramsSelection" ngramsSelection
_ <- if allNgramsSelected || (Set.isEmpty ngramsSelection) then
R2.setIndeterminateCheckbox cb false
else
R2.setIndeterminateCheckbox cb true
pure unit
pure $ H.input { checked: allNgramsSelected
, className: "checkbox"
, on: { change: const $ dispatch $ ToggleSelectAll }
, ref
, type: "checkbox" }
displayRow :: State -> SearchQuery -> NgramsTable -> Maybe NgramsTerm -> Maybe TermList -> NgramsElement -> Boolean displayRow :: State -> SearchQuery -> NgramsTable -> Maybe NgramsTerm -> Maybe TermList -> NgramsElement -> Boolean
displayRow state@{ ngramsChildren displayRow state@{ ngramsChildren
, ngramsLocalPatch , ngramsLocalPatch
......
...@@ -21,9 +21,9 @@ import Effect (Effect) ...@@ -21,9 +21,9 @@ import Effect (Effect)
import Effect.Aff (Aff, launchAff, launchAff_, killFiber) import Effect.Aff (Aff, launchAff, launchAff_, killFiber)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Effect.Exception (error) import Effect.Exception (error)
import Effect.Uncurried (EffectFn1, mkEffectFn1, mkEffectFn2, runEffectFn1) import Effect.Uncurried (EffectFn1, EffectFn2, mkEffectFn1, mkEffectFn2, runEffectFn1, runEffectFn2)
import Effect.Unsafe (unsafePerformEffect) import Effect.Unsafe (unsafePerformEffect)
import FFI.Simple ((..), (...), defineProperty, delay, args2, args3) import FFI.Simple ((..), (...), (.=), defineProperty, delay, args2, args3)
import Partial.Unsafe (unsafePartial) import Partial.Unsafe (unsafePartial)
import React (class ReactPropFields, Children, ReactClass, ReactElement) import React (class ReactPropFields, Children, ReactClass, ReactElement)
import React as React import React as React
...@@ -305,3 +305,9 @@ focus :: Nullable R.Element -> Effect Unit ...@@ -305,3 +305,9 @@ focus :: Nullable R.Element -> Effect Unit
focus nEl = case toMaybe nEl of focus nEl = case toMaybe nEl of
Nothing -> pure unit Nothing -> pure unit
Just el -> el ... "focus" $ [] Just el -> el ... "focus" $ []
setIndeterminateCheckbox :: R.Element -> Boolean -> Effect R.Element
setIndeterminateCheckbox el val = do
log2 "[setIntederminateCheckbox] el" el
log2 "[setIntederminateCheckbox] val" val
pure $ (el .= "indeterminate") val
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