{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, ConstraintKinds #-}
{-# LANGUAGE Safe #-}
module SDP.SortM
(
SortM (..), SortM1, sortM, sortMOn, sortedM, sortedMOn
)
where
import Prelude ()
import SDP.SafePrelude
default ()
class SortM m s e | s -> m, s -> e
where
{-# MINIMAL sortedMBy, sortMBy #-}
sortedMBy :: (e -> e -> Bool) -> s -> m Bool
sortMBy :: Compare e -> s -> m ()
type SortM1 m s e = SortM m (s e) e
sortedM :: (SortM m s e, Ord e) => s -> m Bool
sortedM :: s -> m Bool
sortedM = (e -> e -> Bool) -> s -> m Bool
forall (m :: * -> *) s e.
SortM m s e =>
(e -> e -> Bool) -> s -> m Bool
sortedMBy e -> e -> Bool
forall a. Ord a => a -> a -> Bool
(<=)
sortedMOn :: (SortM m s e, Ord o) => (e -> o) -> s -> m Bool
sortedMOn :: (e -> o) -> s -> m Bool
sortedMOn = (e -> e -> Bool) -> s -> m Bool
forall (m :: * -> *) s e.
SortM m s e =>
(e -> e -> Bool) -> s -> m Bool
sortedMBy ((e -> e -> Bool) -> s -> m Bool)
-> ((e -> o) -> e -> e -> Bool) -> (e -> o) -> s -> m Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((o -> o -> Bool) -> (e -> o) -> e -> e -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on o -> o -> Bool
forall a. Ord a => a -> a -> Bool
(<=))
sortM :: (SortM m s e, Ord e) => s -> m ()
sortM :: s -> m ()
sortM = Compare e -> s -> m ()
forall (m :: * -> *) s e. SortM m s e => Compare e -> s -> m ()
sortMBy Compare e
forall a. Ord a => a -> a -> Ordering
compare
sortMOn :: (SortM m s e, Ord o) => (e -> o) -> s -> m ()
sortMOn :: (e -> o) -> s -> m ()
sortMOn = Compare e -> s -> m ()
forall (m :: * -> *) s e. SortM m s e => Compare e -> s -> m ()
sortMBy (Compare e -> s -> m ())
-> ((e -> o) -> Compare e) -> (e -> o) -> s -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (e -> o) -> Compare e
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing