-- | -- Module : Languages.UniquenessPeriods.Vector.PropertiesFuncRepG -- 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. {-# LANGUAGE CPP, BangPatterns #-} module Languages.UniquenessPeriods.Vector.PropertiesFuncRepG ( -- * Functions with 'Int16' procDiverse2I , procDiverse2Ineg -- * Functions with 'Float' , procDiverse2F , procDiverse2Fneg , procRhythmicity23F , procRhythmicity23Fneg , procBothF , procBothFneg , procBothInvF , procBothInvFneg ) where #ifdef __GLASGOW_HASKELL__ #if __GLASGOW_HASKELL__>=710 /* code that applies only to GHC 7.10.* and higher versions */ import GHC.Base (mconcat) #endif #endif import GHC.Int import qualified Data.Vector as VB import qualified Data.Vector.Unboxed as V import String.Languages.UniquenessPeriods.VectorG import Languages.UniquenessPeriods.Vector.PropertiesSyllablesG import Languages.UniquenessPeriods.Vector.PropertiesG import Languages.Rhythmicity import Languages.UniquenessPeriods.Vector.DataG import GHC.Float (int2Float) import Melodics.ByteString.Ukrainian import Languages.Phonetic.Ukrainian.Syllable #ifdef __GLASGOW_HASKELL__ #if __GLASGOW_HASKELL__==708 /* code that applies only to GHC 7.8.* */ mconcat = concat #endif #endif procDiverse2I :: FuncRep (VB.Vector Char) (UniquenessGeneral2 Char) [Int16] procDiverse2I = D2 (uniquenessPeriodsVector3 " 01-" . convertToProperUkrainianV2X) ((:[]) . diverse2) {-# INLINE procDiverse2I #-} -- | Can be used to find out the minimum element. procDiverse2Ineg :: FuncRep (VB.Vector Char) (UniquenessGeneral2 Char) [Int16] procDiverse2Ineg = D2 (uniquenessPeriodsVector3 " 01-" . convertToProperUkrainianV2X) ((:[]) . negate . diverse2) {-# INLINE procDiverse2Ineg #-} procDiverse2F :: FuncRep (VB.Vector Char) (UniquenessGeneral2 Char) [Float] procDiverse2F = D2 (uniquenessPeriodsVector3 " 01-" . convertToProperUkrainianV2X) ((:[]) . int2Float . fromEnum . diverse2) {-# INLINE procDiverse2F #-} procDiverse2Fneg :: FuncRep (VB.Vector Char) (UniquenessGeneral2 Char) [Float] procDiverse2Fneg = D2 (uniquenessPeriodsVector3 " 01-" . convertToProperUkrainianV2X) ((:[]) . int2Float . negate . fromEnum . diverse2) {-# INLINE procDiverse2Fneg #-} procRhythmicity23F :: FuncRep (VB.Vector Char) (UniquenessGeneral2 Char) [Float] procRhythmicity23F = U1 ((:[]) . rhythmicityV0) {-# INLINE procRhythmicity23F #-} -- | Can be used to find out the minimum element. procRhythmicity23Fneg :: FuncRep (VB.Vector Char) (UniquenessGeneral2 Char) [Float] procRhythmicity23Fneg = U1 ((:[]) . negate . rhythmicityV0) {-# INLINE procRhythmicity23Fneg #-} procBothF :: FuncRep (VB.Vector Char) (UniquenessGeneral2 Char) [Float] procBothF = U1 (\v -> let ys = convertToProperUkrainianV2S . VB.map (\x -> if x == '-' then ' ' else x) $ v in (:[]) ((int2Float . fromEnum . diverse2 . uniquenessPeriodsVector3 " 01-" . VB.fromList $ ys)*(evalRhythmicity23 . mconcat . syllableDurations . map (divVwls . reSyllableCntnts . groupSnds . vec2UZPP2s) . vecWords . V.filter (/='0') . V.fromList $ ys))) {-# INLINE procBothF #-} -- | Can be used to find out the minimum element. procBothFneg :: FuncRep (VB.Vector Char) (UniquenessGeneral2 Char) [Float] procBothFneg = U1 (\v -> let ys = convertToProperUkrainianV2S . VB.map (\x -> if x == '-' then ' ' else x) $ v in (:[]) ((int2Float . negate . fromEnum . diverse2 . uniquenessPeriodsVector3 " 01-" . VB.fromList$ ys)*(evalRhythmicity23 . mconcat . syllableDurations . map (divVwls . reSyllableCntnts . groupSnds . vec2UZPP2s) . vecWords . V.filter (/='0') . V.fromList $ ys))) {-# INLINE procBothFneg #-} procBothInvF :: FuncRep (VB.Vector Char) (UniquenessGeneral2 Char) [Float] procBothInvF = U1 (\v -> let !ys = convertToProperUkrainianV2S . VB.map (\x -> if x == '-' then ' ' else x) $ v !zs = uniquenessPeriodsVector3 " 01-" . VB.fromList $ ys in if VB.null zs then (:[]) ((evalRhythmicity23 . mconcat . syllableDurations . map (divVwls . reSyllableCntnts . groupSnds . vec2UZPP2s) . vecWords . V.filter (/='0') . V.fromList $ ys) * (evalRhythmicity23 . mconcat . syllableDurations . map (divVwls . reSyllableCntnts . groupSnds . vec2UZPP2s) . vecWords . V.filter (/='0') . V.fromList $ ys)) else (:[]) ((evalRhythmicity23 . mconcat . syllableDurations . map (divVwls . reSyllableCntnts . groupSnds . vec2UZPP2s) . vecWords . V.filter (/='0') . V.fromList $ ys) / (int2Float . fromEnum . diverse2 $ zs))) {-# INLINE procBothInvF #-} -- | Can be used to find out the minimum element. procBothInvFneg :: FuncRep (VB.Vector Char) (UniquenessGeneral2 Char) [Float] procBothInvFneg = U1 (\v -> let !ys = convertToProperUkrainianV2S . VB.map (\x -> if x == '-' then ' ' else x) $ v !zs = uniquenessPeriodsVector3 " 01-" .VB.fromList $ ys in if VB.null zs then (:[]) (negate (evalRhythmicity23 . mconcat . syllableDurations . map (divVwls . reSyllableCntnts . groupSnds . vec2UZPP2s) . vecWords . V.filter (/='0') . V.fromList $ ys) * (evalRhythmicity23 . mconcat . syllableDurations . map (divVwls . reSyllableCntnts . groupSnds . vec2UZPP2s) . vecWords . V.filter (/='0') . V.fromList $ ys)) else (:[]) ((evalRhythmicity23 . mconcat . syllableDurations . map (divVwls . reSyllableCntnts . groupSnds . vec2UZPP2s) . vecWords . V.filter (/='0') . V.fromList $ ys) / (int2Float . negate . fromEnum . diverse2 $ zs))) {-# INLINE procBothInvFneg #-}