-- |
-- Module      :  Phladiprelio.Filters
-- Copyright   :  (c) OleksandrZhabenko 2020-2023
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  oleksandr.zhabenko@yahoo.com
--
-- A module allows to change the structure of the function output for the functions of
-- elements from 'RealFrac' class. At the moment only the equal intervals are supported.
-- Uses less dependencies than its former analogue package @uniqueness-periods-vector-filters@.
--
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE Strict #-}
{-# OPTIONS_HADDOCK -show-extensions #-}

module Phladiprelio.Filters (
  -- * One interval used
  intervalNRealFrac
  , unsafeTransfer1I5
  , transfer1IEq3
  -- * Several intervals
  , unsafeRearrangeIG
  , unsafeRearrangeIGArr
  , unsafeRearrangeIGV
  -- * Some basic usage examples
  , unsafeSwapIWithMaxI
) where

import GHC.Base
import GHC.Num ((+),(-),(*),abs)
import GHC.Real
import GHC.Int
import Data.Filters.Basic
import GHC.Arr
import CaseBi.Arr
import GHC.List
import Data.List (sort)

-- | Makes a complex interval-based transformation moving the value from its own interval to the corresponding by the list of tuples second element of the
-- respective pair with the first element being the starting number of the interval (numeration of them begins at 1). 
-- Usually, its first elements in the tuples are from the range @[1..n]@. Number of the intervals are given as
-- the third argument and for many cases should not be greater than 10. There do exist several semantical constraints for the possible accurate arguments,
-- but they are not checked. For example, the first argument must be less than the second one; the fifth argument must be located between the first two ones;
-- the third argument must be greater than zero.
unsafeRearrangeIG
  :: (RealFrac b, Integral c) => b
  -> b
  -> c
  -> [(c,c)] -- ^ Must be finite and expected to be not empty, elements must have all different by the first element tuples.
  -> b
  -> b
unsafeRearrangeIG :: forall b c.
(RealFrac b, Integral c) =>
b -> b -> c -> [(c, c)] -> b -> b
unsafeRearrangeIG b
minE b
maxE c
n [(c, c)]
xs b
x
 | forall a. Num a => a -> a
abs (b
minE forall a. Num a => a -> a -> a
- b
maxE) forall a. Ord a => a -> a -> Bool
< b
0.00000001 = b
x
 | Bool
otherwise = b
x forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a b. Ord a => b -> [(a, b)] -> a -> b
getBFstL' c
n0 [(c, c)]
xs c
n0 forall a. Num a => a -> a -> a
- c
n0) forall a. Num a => a -> a -> a
* (b
maxE forall a. Num a => a -> a -> a
- b
minE) forall a. Fractional a => a -> a -> a
/ forall a b. (Integral a, Num b) => a -> b
fromIntegral c
n
      where n0 :: c
n0 = forall b c. (RealFrac b, Integral c) => b -> b -> c -> b -> c
intervalNRealFrac b
minE b
maxE c
n b
x

-- | The more optimized variant of the 'unsafeRearrangeIG', but the 'Array' must  be sorted 
-- in the ascending order by the first element in the tuples.
unsafeRearrangeIGArr
  :: (RealFrac b, Integral c) => b
  -> b
  -> c
  -> Array Int (c,c) -- ^ Must be sorted in the ascending order by the first elements in the tuples  and finite
  -> b
  -> b
unsafeRearrangeIGArr :: forall b c.
(RealFrac b, Integral c) =>
b -> b -> c -> Array Int (c, c) -> b -> b
unsafeRearrangeIGArr b
minE b
maxE c
n Array Int (c, c)
arr b
x
 | forall a. Num a => a -> a
abs (b
minE forall a. Num a => a -> a -> a
- b
maxE) forall a. Ord a => a -> a -> Bool
< b
0.00000001 = b
x
 | Bool
otherwise = b
x forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a b. Ord a => (b, Array Int (a, b)) -> a -> b
getBFst' (c
n0, Array Int (c, c)
arr) c
n0 forall a. Num a => a -> a -> a
- c
n0) forall a. Num a => a -> a -> a
* (b
maxE forall a. Num a => a -> a -> a
- b
minE) forall a. Fractional a => a -> a -> a
/ forall a b. (Integral a, Num b) => a -> b
fromIntegral c
n
      where n0 :: c
n0 = forall b c. (RealFrac b, Integral c) => b -> b -> c -> b -> c
intervalNRealFrac b
minE b
maxE c
n b
x


-- | An unzipped variant of the 'unsafeRearrangeIG' function where the list argument is internally 'zip'ped as the second argument with the @[1..n]@.
-- This allows to shorten the time of the arguments writing. 
unsafeRearrangeIGV
  :: (RealFrac b, Integral c, Ord c) => b
  -> b
  -> c
  -> [c] -- ^ Must be not empty and finite, the elements here greater or equal than the third argument are neglected.
  -> b
  -> b
unsafeRearrangeIGV :: forall b c.
(RealFrac b, Integral c, Ord c) =>
b -> b -> c -> [c] -> b -> b
unsafeRearrangeIGV b
minE b
maxE c
n [c]
xs = forall b c.
(RealFrac b, Integral c) =>
b -> b -> c -> Array Int (c, c) -> b -> b
unsafeRearrangeIGArr b
minE b
maxE c
n Array Int (c, c)
arr
   where ts :: [c]
ts = forall {a}. Eq a => [a] -> [a]
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => [a] -> [a]
sort forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Ord a => a -> a -> Bool
<c
n) forall a b. (a -> b) -> a -> b
$ [c]
xs
         f :: [a] -> [a]
f (a
t:a
u:[a]
ts) 
           | a
t forall a. Eq a => a -> a -> Bool
== a
u = [a] -> [a]
f (a
tforall a. a -> [a] -> [a]
:[a]
ts)
           | Bool
otherwise = a
tforall a. a -> [a] -> [a]
:[a] -> [a]
f(a
uforall a. a -> [a] -> [a]
:[a]
ts)
         f [a]
ts = [a]
ts
         ks :: [(c, c)]
ks = forall a b. [a] -> [b] -> [(a, b)]
zip [c]
ts (forall a. [a] -> [a]
cycle [c
n]) forall a. Monoid a => a -> a -> a
`mappend` [(c
n,forall a. [a] -> a
head [c]
xs)]
         l :: Int
l = forall a. [a] -> Int
length [c]
ts
         arr :: Array Int (c, c)
arr = forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,Int
l) [(c, c)]
ks
{-# INLINE unsafeRearrangeIGV #-}

-- | Swaps the k-th inner interval values with the maximum one's (that is the n-th one) values.
unsafeSwapIWithMaxI
  :: (RealFrac b, Integral c) => b
  -> b
  -> c -- ^ It is expected to be greater than 0, though this is not checked.
  -> c -- ^ It is expected to be less than the previous argument, but greater than 0, though this is not checked.
  -> b -- ^ It is expected to lie between the first two arguments, though this is not checked.
  -> b
unsafeSwapIWithMaxI :: forall b c. (RealFrac b, Integral c) => b -> b -> c -> c -> b -> b
unsafeSwapIWithMaxI b
minE b
maxE c
n c
k = forall b c.
(RealFrac b, Integral c) =>
b -> b -> c -> [(c, c)] -> b -> b
unsafeRearrangeIG b
minE b
maxE c
n [(c
k,c
n),(c
n,c
k)]
{-# INLINE unsafeSwapIWithMaxI #-}