-- | -- Module : Phonetic.Languages.Filters -- Copyright : (c) OleksandrZhabenko 2020-2022 -- 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@. -- module Phonetic.Languages.Filters ( -- * One interval used intervalNRealFrac , unsafeTransfer1I5 , transfer1IEq3 -- * Several intervals , unsafeRearrangeIG , unsafeRearrangeIGArr , unsafeRearrangeIGV -- * Some basic usage examples , unsafeSwapIWithMaxI , unsafeSwapVecIWithMaxI ) where import Data.Filters.Basic import GHC.Arr import CaseBi.Arr import Data.Monoid (mappend) 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 minE maxE n xs x | minE == maxE = x | otherwise = x + fromIntegral (getBFstL' n0 xs n0 - n0) * (maxE - minE) / fromIntegral n where n0 = intervalNRealFrac minE maxE n 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 minE maxE n arr x | minE == maxE = x | otherwise = x + fromIntegral (getBFst' (n0, arr) n0 - n0) * (maxE - minE) / fromIntegral n where n0 = intervalNRealFrac minE maxE n 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 minE maxE n xs = unsafeRearrangeIGArr minE maxE n arr where ts = f . sort . filter ( 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 minE maxE n k = unsafeRearrangeIG minE maxE n [(k,n),(n,k)] {-# 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, Ord c) => b -> b -> c -- ^ It is expected to be greater than 0, though this is not checked. -> [c] -- ^ It is expected the non-empty finite list (indices are counted in it starting with 1 opposed to the usual behaviour for lists) and numbers here should be the numbers of the intervals less than n. -> b -- ^ It is expected to be less than the second argument (if it expected to be probably changed). -> b unsafeSwapVecIWithMaxI = unsafeRearrangeIGV {-# INLINE unsafeSwapVecIWithMaxI #-} {-# DEPRECATED unsafeSwapVecIWithMaxI "Is provided here for the compatibility with the previous ones versions. Please, use just 'unsafeRearrangeIGV' instead" #-}