-- |
-- Module      :  Phonetic.Languages.Filters
-- Copyright   :  (c) OleksandrZhabenko 2020
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  olexandr543@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@.
-- Reimports the functions from the @filters-basic@ module except the auxiliary zero2One,
-- so if you intend to use the functionality of both of them, use just this one.

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

import Data.Filters.Basic
import GHC.Arr
import CaseBi.Arr
--import qualified Data.Vector as V

-- | 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). The list argument must be sorted
-- by the first argument in the ascending order. 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)]
  -> b
  -> b
unsafeRearrangeIG :: b -> b -> c -> [(c, c)] -> b -> b
unsafeRearrangeIG b
minE b
maxE c
n [(c, c)]
xs b
x
 | b
minE b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== b
maxE = b
x
 | Bool
otherwise = b
x b -> b -> b
forall a. Num a => a -> a -> a
+ c -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral (c -> [(c, c)] -> c -> c
forall a b. Ord a => b -> [(a, b)] -> a -> b
getBFstL' c
n0 [(c, c)]
xs c
n0 c -> c -> c
forall a. Num a => a -> a -> a
- c
n0) b -> b -> b
forall a. Num a => a -> a -> a
* (b
maxE b -> b -> b
forall a. Num a => a -> a -> a
- b
minE) b -> b -> b
forall a. Fractional a => a -> a -> a
/ c -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral c
n
      where n0 :: c
n0 = b -> b -> c -> b -> c
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) => b
  -> b
  -> c
  -> [c]
  -> b
  -> b
unsafeRearrangeIGV :: b -> b -> c -> [c] -> b -> b
unsafeRearrangeIGV b
minE b
maxE c
n [c]
xs = b -> b -> c -> [(c, c)] -> b -> b
forall b c.
(RealFrac b, Integral c) =>
b -> b -> c -> [(c, c)] -> b -> b
unsafeRearrangeIG b
minE b
maxE c
n ([(c, c)] -> b -> b) -> ([c] -> [(c, c)]) -> [c] -> b -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [c] -> [c] -> [(c, c)]
forall a b. [a] -> [b] -> [(a, b)]
zip [c
1..c
n] ([c] -> b -> b) -> [c] -> b -> b
forall a b. (a -> b) -> a -> b
$ [c]
xs
{-# 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 :: b -> b -> c -> c -> b -> b
unsafeSwapIWithMaxI b
minE b
maxE c
n c
k = b -> b -> c -> [c] -> b -> b
forall b c.
(RealFrac b, Integral c) =>
b -> b -> c -> [c] -> b -> b
unsafeRearrangeIGV b
minE b
maxE c
n ([c] -> b -> b) -> ([c] -> [c]) -> [c] -> b -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (c -> c) -> [c] -> [c]
forall a b. (a -> b) -> [a] -> [b]
map (c -> c -> c -> c
forall a. (Eq a, Num a) => a -> a -> a -> a
f c
k c
n) ([c] -> b -> b) -> [c] -> b -> b
forall a b. (a -> b) -> a -> b
$ [c
0..c
n c -> c -> c
forall a. Num a => a -> a -> a
- c
1]
  where f :: a -> a -> a -> a
f a
k a
n a
x
         | a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
k a -> a -> a
forall a. Num a => a -> a -> a
- a
1 = a
n a -> a -> a
forall a. Num a => a -> a -> a
- a
1
         | a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
n a -> a -> a
forall a. Num a => a -> a -> a
- a
1 = a
k a -> a -> a
forall a. Num a => a -> a -> a
- a
1
         | Bool
otherwise = a
x
        {-# INLINE f #-}
{-# INLINE unsafeSwapIWithMaxI #-}

-- | Swaps the inner intervals values (given by the list of elements of the data type that has an instance of the
-- 'Integral' class that represent numbers-indices starting from 1 to n) with the maximum one's
-- (that is the n-th one) values. The list must be not empty and sorted in the ascending order, though it is not checked. Be aware that this can
-- significantly change the density of the values and break some other properties for distributions.
unsafeSwapVecIWithMaxI
  :: (RealFrac b, Integral c) => b
  -> b
  -> c -- ^ It is expected to be greater than 0, though this is not checked.
  -> [c] -- ^ It is expected the list to be sorted in the ascending order (indices are counted in it starting with 1 opposed to the usual behaviour for lists and are the numbers of the intervals in the range from 1 to n), and besides all the elements to be less than the previous argument, greater than 0 and to be not pairwise equal, though it is not checked.
  -> b -- ^ It is expected to lie between the first two arguments, though this is not checked.
  -> b
unsafeSwapVecIWithMaxI :: b -> b -> c -> [c] -> b -> b
unsafeSwapVecIWithMaxI b
minE b
maxE c
n [c]
xs = b -> b -> c -> [c] -> b -> b
forall b c.
(RealFrac b, Integral c) =>
b -> b -> c -> [c] -> b -> b
unsafeRearrangeIGV b
minE b
maxE c
n ((c -> c) -> [c] -> [c]
forall a b. (a -> b) -> [a] -> [b]
map c -> c
h [c
0..c
n c -> c -> c
forall a. Num a => a -> a -> a
- c
1])
  where h :: c -> c
h c
i
         | Bool -> [(c, Bool)] -> c -> Bool
forall a b. Ord a => b -> [(a, b)] -> a -> b
getBFstL' Bool
False ([c] -> [Bool] -> [(c, Bool)]
forall a b. [a] -> [b] -> [(a, b)]
zip ((c -> c) -> [c] -> [c]
forall a b. (a -> b) -> [a] -> [b]
map (c -> c -> c
forall a. Num a => a -> a -> a
+ (-c
1)) [c]
xs) ([Bool] -> [(c, Bool)]) -> (Bool -> [Bool]) -> Bool -> [(c, Bool)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Bool -> [Bool]
forall a. Int -> a -> [a]
replicate (c -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral c
n) (Bool -> [(c, Bool)]) -> Bool -> [(c, Bool)]
forall a b. (a -> b) -> a -> b
$ Bool
True) c
i = c
n c -> c -> c
forall a. Num a => a -> a -> a
- c
1
         | c
i c -> c -> Bool
forall a. Eq a => a -> a -> Bool
== c
n c -> c -> c
forall a. Num a => a -> a -> a
- c
1 = [c] -> c
forall a. [a] -> a
head [c]
xs
         | Bool
otherwise = c
i
{-# INLINE unsafeSwapVecIWithMaxI #-}