-- | -- Module : Languages.UniquenessPeriods.Vector.PropertiesFuncRep -- 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.PropertiesFuncRep where import qualified Data.Vector as V import String.Languages.UniquenessPeriods.Vector import Languages.UniquenessPeriods.Vector.PropertiesSyllables import Languages.UniquenessPeriods.Vector.Properties import Languages.Rhythmicity import Languages.UniquenessPeriods.Vector.Data import Languages.Phonetic.Ukrainian.PrepareText import GHC.Float (int2Float) import Melodics.Ukrainian (convertToProperUkrainian) procDiverse2I :: FuncRep String (UniquenessGeneral2 Char) [Int] procDiverse2I = D2 (uniquenessPeriodsVector3 " 01-" . aux0 . convertToProperUkrainian) (justOneValue2Property . diverse2) {-# INLINE procDiverse2I #-} procDiverse2F :: FuncRep String (UniquenessGeneral2 Char) [Float] procDiverse2F = D2 (uniquenessPeriodsVector3 " 01-" . aux0 . convertToProperUkrainian) (justOneValue2Property . int2Float . diverse2) {-# INLINE procDiverse2F #-} procRhythmicity23F :: FuncRep String (UniquenessGeneral2 Char) [Float] procRhythmicity23F = U1 (justOneValue2Property . rhythmicity0) {-# INLINE procRhythmicity23F #-} procBothF :: FuncRep String (UniquenessGeneral2 Char) [Float] procBothF = U1 (\xs -> [(int2Float . diverse2 . uniquenessPeriodsVector3 " 01-" . aux0 . convertToProperUkrainian $ xs)*(rhythmicity0 xs)]) {-# INLINE procBothF #-}