-- |
-- Module      :  Data.MinMax3Plus.Preconditions
-- Copyright   :  (c) OleksandrZhabenko 2020-2023
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  oleksandr.zhabenko@yahoo.com
--
-- Functions to find both minimum and maximum elements of the 'F.Foldable' structure of the 'Ord'ered elements. With the preconditions that the
-- structure at least have enough elements (this is contrary to the functions from the module Data.MinMax not checked internally).

{-# LANGUAGE NoImplicitPrelude #-}

module Data.MinMax3Plus.Preconditions where

import GHC.Base
import Data.SubG
import qualified Data.Foldable as F
import qualified Data.List as L (sortBy)

-- | Given a finite structure returns a tuple with two minimum elements
-- and three maximum elements.
-- Uses just two passes through the structure, so may be more efficient than some other approaches.
minMax23C :: (Ord a, InsertLeft t a, Monoid (t a)) => t a -> ((a,a), (a,a,a))
minMax23C :: forall a (t :: * -> *).
(Ord a, InsertLeft t a, Monoid (t a)) =>
t a -> ((a, a), (a, a, a))
minMax23C = forall a (t :: * -> *).
(Ord a, InsertLeft t a, Monoid (t a)) =>
(a -> a -> Ordering) -> t a -> ((a, a), (a, a, a))
minMax23ByC forall a. Ord a => a -> a -> Ordering
compare
{-# INLINE minMax23C #-}

-- | A variant of the 'minMax23C' where you can specify your own comparison function.
minMax23ByC :: (Ord a, InsertLeft t a, Monoid (t a)) => (a -> a -> Ordering) -> t a -> ((a,a), (a,a,a))
minMax23ByC :: forall a (t :: * -> *).
(Ord a, InsertLeft t a, Monoid (t a)) =>
(a -> a -> Ordering) -> t a -> ((a, a), (a, a, a))
minMax23ByC a -> a -> Ordering
g t a
xs =
  forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr a -> ((a, a), (a, a, a)) -> ((a, a), (a, a, a))
f ((a
n,a
p),(a
q,a
r,a
s)) forall a b. (a -> b) -> a -> b
$ t a
str1
    where (t a
str1,t a
str2) = forall b (t :: * -> *) a.
(Integral b, InsertLeft t a, Monoid (t a)) =>
b -> t a -> (t a, t a)
splitAtEndG Integer
5 t a
xs
          [a
n,a
p,a
q,a
r,a
s] = forall a. (a -> a -> Ordering) -> [a] -> [a]
L.sortBy a -> a -> Ordering
g forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList forall a b. (a -> b) -> a -> b
$ t a
str2
          f :: a -> ((a, a), (a, a, a)) -> ((a, a), (a, a, a))
f a
z ((a
x,a
y),(a
t,a
w,a
u))
            | a -> a -> Ordering
g a
z a
y forall a. Eq a => a -> a -> Bool
== Ordering
LT = if a -> a -> Ordering
g a
z a
x forall a. Eq a => a -> a -> Bool
== Ordering
GT then ((a
x,a
z),(a
t,a
w,a
u)) else ((a
z,a
x),(a
t,a
w,a
u))
            | a -> a -> Ordering
g a
z a
t forall a. Eq a => a -> a -> Bool
== Ordering
GT = if a -> a -> Ordering
g a
z a
w forall a. Eq a => a -> a -> Bool
== Ordering
LT then ((a
x,a
y),(a
z,a
w,a
u)) else if a -> a -> Ordering
g a
z a
u forall a. Eq a => a -> a -> Bool
== Ordering
LT then ((a
x,a
y),(a
w,a
z,a
u)) else ((a
x,a
y),(a
t,a
w,a
u))
            | Bool
otherwise = ((a
x,a
y),(a
t,a
w,a
u))

-- | Given a finite structure returns a tuple with three minimum elements
-- and two maximum elements. Uses just two passes through the structure, so may be more efficient than some other approaches.
minMax32C :: (Ord a, InsertLeft t a, Monoid (t a)) => t a -> ((a,a,a), (a,a))
minMax32C :: forall a (t :: * -> *).
(Ord a, InsertLeft t a, Monoid (t a)) =>
t a -> ((a, a, a), (a, a))
minMax32C = forall a (t :: * -> *).
(Ord a, InsertLeft t a, Monoid (t a)) =>
(a -> a -> Ordering) -> t a -> ((a, a, a), (a, a))
minMax32ByC forall a. Ord a => a -> a -> Ordering
compare
{-# INLINE minMax32C #-}

-- | A variant of the 'minMax32C' where you can specify your own comparison function.
minMax32ByC :: (Ord a, InsertLeft t a, Monoid (t a)) => (a -> a -> Ordering) -> t a -> ((a,a,a), (a,a))
minMax32ByC :: forall a (t :: * -> *).
(Ord a, InsertLeft t a, Monoid (t a)) =>
(a -> a -> Ordering) -> t a -> ((a, a, a), (a, a))
minMax32ByC a -> a -> Ordering
g t a
xs =
  forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr a -> ((a, a, a), (a, a)) -> ((a, a, a), (a, a))
f ((a
n,a
m,a
p),(a
q,a
r)) forall a b. (a -> b) -> a -> b
$ t a
str1
    where (t a
str1,t a
str2) = forall b (t :: * -> *) a.
(Integral b, InsertLeft t a, Monoid (t a)) =>
b -> t a -> (t a, t a)
splitAtEndG Integer
5 t a
xs
          [a
n,a
m,a
p,a
q,a
r] = forall a. (a -> a -> Ordering) -> [a] -> [a]
L.sortBy a -> a -> Ordering
g forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList forall a b. (a -> b) -> a -> b
$ t a
str2
          f :: a -> ((a, a, a), (a, a)) -> ((a, a, a), (a, a))
f a
z ((a
x,a
y,a
u),(a
t,a
w))
            | a -> a -> Ordering
g a
z a
u forall a. Eq a => a -> a -> Bool
== Ordering
LT = if a -> a -> Ordering
g a
z a
y forall a. Eq a => a -> a -> Bool
== Ordering
GT then ((a
x,a
y,a
z),(a
t,a
w)) else if a -> a -> Ordering
g a
z a
x forall a. Eq a => a -> a -> Bool
== Ordering
GT then ((a
x,a
z,a
y),(a
t,a
w)) else ((a
z,a
x,a
y),(a
t,a
w))
            | a -> a -> Ordering
g a
z a
t forall a. Eq a => a -> a -> Bool
== Ordering
GT = if a -> a -> Ordering
g a
z a
w forall a. Eq a => a -> a -> Bool
== Ordering
LT then ((a
x,a
y,a
u),(a
z,a
w)) else ((a
x,a
y,a
u),(a
w,a
z))
            | Bool
otherwise = ((a
x,a
y,a
u),(a
t,a
w))

-- | Given a finite structure returns a tuple with three minimum elements
-- and three maximum elements. Uses just two passes through the structure, so may be more efficient than some other approaches.
minMax33C :: (Ord a, InsertLeft t a, Monoid (t a)) => t a -> ((a,a,a), (a,a,a))
minMax33C :: forall a (t :: * -> *).
(Ord a, InsertLeft t a, Monoid (t a)) =>
t a -> ((a, a, a), (a, a, a))
minMax33C = forall a (t :: * -> *).
(Ord a, InsertLeft t a, Monoid (t a)) =>
(a -> a -> Ordering) -> t a -> ((a, a, a), (a, a, a))
minMax33ByC forall a. Ord a => a -> a -> Ordering
compare
{-# INLINE minMax33C #-}

-- | A variant of the 'minMax33C' where you can specify your own comparison function.
minMax33ByC :: (Ord a, InsertLeft t a, Monoid (t a)) => (a -> a -> Ordering) -> t a -> ((a,a,a), (a,a,a))
minMax33ByC :: forall a (t :: * -> *).
(Ord a, InsertLeft t a, Monoid (t a)) =>
(a -> a -> Ordering) -> t a -> ((a, a, a), (a, a, a))
minMax33ByC a -> a -> Ordering
g t a
xs =
  forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
F.foldr a -> ((a, a, a), (a, a, a)) -> ((a, a, a), (a, a, a))
f ((a
n,a
m,a
p),(a
q,a
r,a
s)) forall a b. (a -> b) -> a -> b
$ t a
str1
    where (t a
str1,t a
str2) = forall b (t :: * -> *) a.
(Integral b, InsertLeft t a, Monoid (t a)) =>
b -> t a -> (t a, t a)
splitAtEndG Integer
6 t a
xs
          [a
n,a
m,a
p,a
q,a
r,a
s] = forall a. (a -> a -> Ordering) -> [a] -> [a]
L.sortBy a -> a -> Ordering
g forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList forall a b. (a -> b) -> a -> b
$ t a
str2
          f :: a -> ((a, a, a), (a, a, a)) -> ((a, a, a), (a, a, a))
f a
z ((a
x,a
y,a
u),(a
t,a
w,a
k))
            | a -> a -> Ordering
g a
z a
u forall a. Eq a => a -> a -> Bool
== Ordering
LT = if a -> a -> Ordering
g a
z a
y forall a. Eq a => a -> a -> Bool
== Ordering
GT then ((a
x,a
y,a
z),(a
t,a
w,a
k)) else if a -> a -> Ordering
g a
z a
x forall a. Eq a => a -> a -> Bool
== Ordering
GT then ((a
x,a
z,a
y),(a
t,a
w,a
k)) else ((a
z,a
x,a
y),(a
t,a
w,a
k))
            | a -> a -> Ordering
g a
z a
t forall a. Eq a => a -> a -> Bool
== Ordering
GT = if a -> a -> Ordering
g a
z a
w forall a. Eq a => a -> a -> Bool
== Ordering
LT then ((a
x,a
y,a
u),(a
z,a
w,a
k)) else if a -> a -> Ordering
g a
z a
k forall a. Eq a => a -> a -> Bool
== Ordering
LT then ((a
x,a
y,a
u),(a
w,a
z,a
k)) else ((a
x,a
y,a
u),(a
w,a
k,a
z))
            | Bool
otherwise = ((a
x,a
y,a
u),(a
t,a
w,a
k))