-- | -- Module : Languages.UniquenessPeriods.Vector.Properties -- Copyright : (c) OleksandrZhabenko 2020 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Generalization of the functionality of the DobutokO.Poetry.Norms -- and DobutokO.Poetry.Norms.Extended modules -- from the @dobutokO-poetry@ package. module Languages.UniquenessPeriods.Vector.Properties where import qualified Data.Vector as V import String.Languages.UniquenessPeriods.Vector -- | The function is inteded to be used after 'uniquenessPeriodsVector2' application to obtain the first argument. So generally, it is used as follows: -- > -- > diverse . uniquenessPeriodsVector2 y whspss $ v -- -- The maximum value of the function corresponds to possibly more smoothly changing and mixing elements in the list. If they are used to represent -- sounds (especially some text, may be poetic) then the resulting maximum possible 'diverse' value corresponds to more \"diverse\" (phonetically) text intervals. -- Is somewhat similar to the @norm4@ function from the DobutokO.Poetyr.Norms module from @dobutokO-poetry@ package -- See: https://hackage.haskell.org/package/dobutokO-poetry-general-0.1.0.0/docs/DobutokO-Poetry-Norms.html. diverse :: Eq a => UniquenessGeneral2 a -- ^ Is gotten after the application of the 'uniquenessPeriodsVector2'. -> Int -- ^ The resulting value. diverse v | null v = 0 | otherwise = V.sum . V.map (\(x,_) -> if null x then 0::Int else minimum x) $ v