Commit d8729444 authored by Nicolas Pouillard's avatar Nicolas Pouillard

Add a better and more general sortWith

parent 9c4f2849
...@@ -32,7 +32,7 @@ import Gargantext.Components.Category ...@@ -32,7 +32,7 @@ import Gargantext.Components.Category
import Gargantext.Components.Table as T import Gargantext.Components.Table as T
import Gargantext.Ends (Frontends, url) import Gargantext.Ends (Frontends, url)
import Gargantext.Hooks.Loader (useLoaderWithCacheAPI, HashedResponse(..)) import Gargantext.Hooks.Loader (useLoaderWithCacheAPI, HashedResponse(..))
import Gargantext.Utils.Seq (sortWith) as Seq import Gargantext.Utils (sortWith)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Routes as Routes import Gargantext.Routes as Routes
import Gargantext.Routes (SessionRoute(NodeAPI)) import Gargantext.Routes (SessionRoute(NodeAPI))
...@@ -377,12 +377,12 @@ pagePaintCpt = R.hooksComponentWithModule thisModule "pagePaintCpt" cpt where ...@@ -377,12 +377,12 @@ pagePaintCpt = R.hooksComponentWithModule thisModule "pagePaintCpt" cpt where
getCategory (localCategories /\ _) {_id, category} = fromMaybe category (localCategories ^. at _id) getCategory (localCategories /\ _) {_id, category} = fromMaybe category (localCategories ^. at _id)
orderWith = orderWith =
case convOrderBy (fst params).orderBy of case convOrderBy (fst params).orderBy of
Just DateAsc -> Seq.sortWith \(DocumentsView { date }) -> date Just DateAsc -> sortWith \(DocumentsView { date }) -> date
Just DateDesc -> Seq.sortWith \(DocumentsView { date }) -> Down date Just DateDesc -> sortWith \(DocumentsView { date }) -> Down date
Just SourceAsc -> Seq.sortWith \(DocumentsView { source }) -> Str.toLower source Just SourceAsc -> sortWith \(DocumentsView { source }) -> Str.toLower source
Just SourceDesc -> Seq.sortWith \(DocumentsView { source }) -> Down $ Str.toLower source Just SourceDesc -> sortWith \(DocumentsView { source }) -> Down $ Str.toLower source
Just TitleAsc -> Seq.sortWith \(DocumentsView { title }) -> Str.toLower title Just TitleAsc -> sortWith \(DocumentsView { title }) -> Str.toLower title
Just TitleDesc -> Seq.sortWith \(DocumentsView { title }) -> Down $ Str.toLower title Just TitleDesc -> sortWith \(DocumentsView { title }) -> Down $ Str.toLower title
_ -> identity -- the server ordering is enough here _ -> identity -- the server ordering is enough here
filteredRows = T.filterRows { params: fst params } $ orderWith $ A.toUnfoldable documents filteredRows = T.filterRows { params: fst params } $ orderWith $ A.toUnfoldable documents
rows localCategories = row <$> filteredRows rows localCategories = row <$> filteredRows
......
...@@ -42,7 +42,7 @@ import Gargantext.Prelude (class Show, Unit, bind, const, discard, identity, map ...@@ -42,7 +42,7 @@ import Gargantext.Prelude (class Show, Unit, bind, const, discard, identity, map
import Gargantext.Routes (SessionRoute(..)) as R import Gargantext.Routes (SessionRoute(..)) as R
import Gargantext.Sessions (Session, get) import Gargantext.Sessions (Session, get)
import Gargantext.Types (CTabNgramType, OrderBy(..), SearchQuery, TabType, TermList(..), TermSize, termLists, termSizes) import Gargantext.Types (CTabNgramType, OrderBy(..), SearchQuery, TabType, TermList(..), TermSize, termLists, termSizes)
import Gargantext.Utils (queryMatchesLabel, toggleSet) import Gargantext.Utils (queryMatchesLabel, toggleSet, sortWith)
import Gargantext.Utils.CacheAPI as GUC import Gargantext.Utils.CacheAPI as GUC
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Seq as Seq import Gargantext.Utils.Seq as Seq
...@@ -423,10 +423,10 @@ loadedNgramsTableCpt = R.hooksComponentWithModule thisModule "loadedNgramsTable" ...@@ -423,10 +423,10 @@ loadedNgramsTableCpt = R.hooksComponentWithModule thisModule "loadedNgramsTable"
} }
orderWith = orderWith =
case convOrderBy <$> params.orderBy of case convOrderBy <$> params.orderBy of
Just ScoreAsc -> Seq.sortWith \x -> x ^. _NgramsElement <<< _occurrences Just ScoreAsc -> sortWith \x -> x ^. _NgramsElement <<< _occurrences
Just ScoreDesc -> Seq.sortWith \x -> Down $ x ^. _NgramsElement <<< _occurrences Just ScoreDesc -> sortWith \x -> Down $ x ^. _NgramsElement <<< _occurrences
Just TermAsc -> Seq.sortWith \x -> x ^. _NgramsElement <<< _ngrams Just TermAsc -> sortWith \x -> x ^. _NgramsElement <<< _ngrams
Just TermDesc -> Seq.sortWith \x -> Down $ x ^. _NgramsElement <<< _ngrams Just TermDesc -> sortWith \x -> Down $ x ^. _NgramsElement <<< _ngrams
_ -> 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
......
...@@ -2,13 +2,15 @@ module Gargantext.Utils where ...@@ -2,13 +2,15 @@ module Gargantext.Utils where
import DOM.Simple.Window (window) import DOM.Simple.Window (window)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Foldable (class Foldable, foldr)
import Data.Lens (Lens', lens) import Data.Lens (Lens', lens)
import Data.Newtype (class Newtype, unwrap, wrap) import Data.Newtype (class Newtype, unwrap, wrap)
import Data.Set (Set) import Data.Set (Set)
import Data.Set as Set import Data.Set as Set
import Data.Sequence.Ordered as OSeq
import Data.String as S import Data.String as S
import Data.Unfoldable (class Unfoldable)
import Effect (Effect) import Effect (Effect)
import Effect.Class (liftEffect)
import FFI.Simple ((..)) import FFI.Simple ((..))
import FFI.Simple.Functions (delay) import FFI.Simple.Functions (delay)
import Prelude import Prelude
...@@ -84,5 +86,19 @@ mapLeft _ (Right r) = Right r ...@@ -84,5 +86,19 @@ mapLeft _ (Right r) = Right r
location :: Effect String location :: Effect String
location = delay unit $ \_ -> pure $ window .. "location" location = delay unit $ \_ -> pure $ window .. "location"
data On a b = On a b
instance eqOn :: Eq a => Eq (On a b) where
eq (On x _) (On y _) = eq x y
instance ordOn :: Ord a => Ord (On a b) where
compare (On x _) (On y _) = compare x y
-- same as
-- https://github.com/purescript/purescript-arrays/blob/v5.3.1/src/Data/Array.purs#L715-L715
sortWith :: forall a b f. Functor f =>
Foldable f =>
Unfoldable f =>
Ord b =>
(a -> b) -> f a -> f a
sortWith f = map (\(On _ y) -> y) <<< OSeq.toUnfoldable <<< foldr (\x -> OSeq.insert (On (f x) x)) OSeq.empty
\ No newline at end of file
module Gargantext.Utils.Seq where module Gargantext.Utils.Seq (mapMaybe) where
import Data.Array as Array import Data.Maybe (Maybe, maybe)
import Data.Maybe import Data.Sequence (Seq, concatMap, empty, singleton)
import Data.Sequence
import Data.Tuple
import Gargantext.Prelude import Gargantext.Prelude ((<<<))
mapMaybe :: forall a b. (a -> Maybe b) -> Seq a -> Seq b mapMaybe :: forall a b. (a -> Maybe b) -> Seq a -> Seq b
mapMaybe f = go empty mapMaybe f = concatMap (maybe empty singleton <<< f)
where
go acc s =
case uncons s of
Nothing -> acc
Just (Tuple x xs) ->
case f x of
Nothing -> go acc xs
Just y -> go (cons y acc) xs
-- same as
-- https://github.com/purescript/purescript-arrays/blob/v5.3.1/src/Data/Array.purs#L715-L715
sortWith :: forall a b. Ord b => (a -> b) -> Seq a -> Seq a
sortWith f l = Array.toUnfoldable $ Array.sortBy (comparing f) $ Array.fromFoldable l
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