{-# OPTIONS_GHC -XFlexibleContexts #-} -- | A number of handy functions, type aliases, and reexports all having to do with ordering operations. module Data.RangeMin.Internal.HandyOrdering(Comparator, orderPairBy, orderPair, minBy, maxBy, maximumBy, minimumBy, comparing, lexCompare, lexComparing, listRangeBy, listRange) where import Data.Monoid import Data.List(maximumBy, minimumBy) import Data.RangeMin.Internal.Combinators(on) -- | A handy shorthand for a frequently occurring function. type Comparator e = e -> e -> Ordering -- | @comparing f (x y)@ is equivalent to @compare (f x) (f y)@. comparing :: Ord b => (a -> b) -> Comparator a comparing f = compare `on` f -- | @orderPairBy cmp (x, y)@ is equivalent to @if cmp x y == GT then (y, x) else (x, y)@. orderPairBy :: Comparator e -> (e, e) -> (e, e) orderPairBy cmp (x,y) = if cmp x y == GT then (y,x) else (x,y) -- | @orderPairBy cmp (x, y)@ is equivalent to @if x <= y then (y, x) else (x, y)@. orderPair :: Ord e => (e, e) -> (e, e) orderPair (x,y) = if x <= y then (x, y) else (y, x) -- | @minBy cmp x y@ returns the smaller of @x@ and @y@ by the specified comparator. minBy :: Comparator e -> e -> e -> e minBy cmp x y = if cmp x y == GT then y else x -- | @maxBy cmp x y@ returns the larger of @x@ and @y@ by the specified comparator. maxBy :: Comparator e -> e -> e -> e maxBy = minBy . flip -- | @lexCompare cmp1 cmp2@ gives a comparator that lexicographically orders first by @cmp1@ then by @cmp2@. lexCompare :: Comparator e -> Comparator e -> Comparator e lexCompare cmp1 cmp2 = \ x y -> cmp1 x y `mappend` cmp2 x y lexComparing :: (Ord a, Ord b) => (e -> a) -> (e -> b) -> Comparator e lexComparing f1 f2 = lexCompare (comparing f1) (comparing f2) minimax :: Comparator e -> e -> (Maybe (e, e), Maybe e) -> (Maybe (e, e), Maybe e) minimax cmp x (minmax, Nothing) = (minmax, Just x) minimax cmp x (Nothing, Just y) = (Just (orderPairBy cmp (x, y)), Nothing) minimax cmp x (Just (mi, ma), Just y) = let (x', y') = orderPairBy cmp (x, y) in (Just (minBy cmp x' mi, maxBy cmp y' ma), Nothing) {-# INLINE listRangeBy #-} listRangeBy :: Comparator e -> [e] -> Maybe (e, e) listRangeBy cmp l = case foldr (minimax cmp) (Nothing, Nothing) l of (Nothing, Just x) -> Just (x, x) -- only one element (Nothing, Nothing) -> Nothing -- no elements (Just p, Nothing) -> Just p (Just (mi, ma), Just x) -> Just (if cmp x mi == GT then (mi, maxBy cmp x ma) else (x, ma)) listRange :: Ord e => [e] -> Maybe (e, e) listRange = listRangeBy compare listRangeWith :: Ord f => (e -> f) -> [e] -> Maybe (e, e) listRangeWith = listRangeBy . comparing