{-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Phladiprelio.Ukrainian.PropertiesFuncRepG24 -- Copyright : (c) Oleksandr Zhabenko 2020-2023 -- License : MIT -- Stability : Experimental -- Maintainer : oleksandr.zhabenko@yahoo.com -- -- Generalization of the functionality of the DobutokO.Poetry.Norms -- and DobutokO.Poetry.Norms.Extended modules -- from the @dobutokO-poetry@ package. Instead of vectors, uses arrays. {-# LANGUAGE NoImplicitPrelude #-} module Phladiprelio.Ukrainian.PropertiesFuncRepG24 where import GHC.Base import Phladiprelio.Ukrainian.Common import Phladiprelio.Ukrainian.PropertiesFuncRepG2Common import Phladiprelio.Basis import qualified Phladiprelio.Ukrainian.SyllableDouble as SD import Phladiprelio.Ukrainian.Melodics import GHC.Arr (Array) import GHC.Int (Int8) import Phladiprelio.Ukrainian.Emphasis import Phladiprelio.Coeffs import Phladiprelio.Rhythmicity.Factor procBothFTupG :: Int -> Coeffs2 -> Array Int (Int8, Bool) -> Array Int (Int8, Bool) -> Array Int (Int8, Bool) -> Array Int (Int8, Bool) -> Array Int ([Int8], Bool) -> Array Int ([Int8], Int8) -> Array Int (Int8, FlowSound -> Sound8) -> Array Int (Int8, Bool) -> Array Int ([Int8], Bool) -> Array Int ([Int8], Bool) -> Array Int ([Int8], Bool) -> Array Int (Int8, [Int8]) -> Array Int (Char,Int8) -> Array Int (Int8,[Int8]) -> Array Int (Char, Bool) -> Array Int (Char, Bool) -> Array Int (Int8,Bool) -> (Double -> Double) -> FlowSound -> FuncRep2 ReadyForConstructionUkr Double Double procBothFTupG n coeffs = procB2FTup coeffs (case n of 1 -> SD.syllableDurationsD 2 -> SD.syllableDurationsD2 3 -> SD.syllableDurationsD3 4 -> SD.syllableDurationsD4) {-# INLINE procBothFTupG #-} procBothFTup = procBothFTupG 1 {-# INLINE procBothFTup #-} procBoth2FTup = procBothFTupG 2 {-# INLINE procBoth2FTup #-} procBoth3FTup = procBothFTupG 3 {-# INLINE procBoth3FTup #-} procBoth4FTup = procBothFTupG 4 {-# INLINE procBoth4FTup #-} procBothFFTupG :: Int -> Factors -> Double -> Coeffs2 -> Array Int (Int8, Bool) -> Array Int (Int8, Bool) -> Array Int (Int8, Bool) -> Array Int (Int8, Bool) -> Array Int ([Int8], Bool) -> Array Int ([Int8], Int8) -> Array Int (Int8, FlowSound -> Sound8) -> Array Int (Int8, Bool) -> Array Int ([Int8], Bool) -> Array Int ([Int8], Bool) -> Array Int ([Int8], Bool) -> Array Int (Int8, [Int8]) -> Array Int (Char,Int8) -> Array Int (Int8,[Int8]) -> Array Int (Char, Bool) -> Array Int (Char, Bool) -> Array Int (Int8,Bool) -> (Double -> Double) -> FlowSound -> FuncRep2 ReadyForConstructionUkr Double Double procBothFFTupG n ff k coeffs = procB2FFTup ff k coeffs (case n of 1 -> SD.syllableDurationsD 2 -> SD.syllableDurationsD2 3 -> SD.syllableDurationsD3 4 -> SD.syllableDurationsD4) {-# INLINE procBothFFTupG #-} procBothFFTup = procBothFFTupG 1 {-# INLINE procBothFFTup #-} procBoth2FFTup = procBothFFTupG 2 {-# INLINE procBoth2FFTup #-} procBoth3FFTup = procBothFFTupG 3 {-# INLINE procBoth3FFTup #-} procBoth4FFTup = procBothFFTupG 4 {-# INLINE procBoth4FFTup #-} procBothInvFTupG :: Int -> Coeffs2 -> Array Int (Int8, Bool) -> Array Int (Int8, Bool) -> Array Int (Int8, Bool) -> Array Int (Int8, Bool) -> Array Int ([Int8], Bool) -> Array Int ([Int8], Int8) -> Array Int (Int8, FlowSound -> Sound8) -> Array Int (Int8, Bool) -> Array Int ([Int8], Bool) -> Array Int ([Int8], Bool) -> Array Int ([Int8], Bool) -> Array Int (Int8, [Int8]) -> Array Int (Char,Int8) -> Array Int (Int8,[Int8]) -> Array Int (Char, Bool) -> Array Int (Char, Bool) -> Array Int (Int8,Bool) -> (Double -> Double) -> FlowSound -> FuncRep2 ReadyForConstructionUkr Double Double procBothInvFTupG n coeffs = procB2InvFTup coeffs (case n of 1 -> SD.syllableDurationsD 2 -> SD.syllableDurationsD2 3 -> SD.syllableDurationsD3 4 -> SD.syllableDurationsD4) {-# INLINE procBothInvFTupG #-} procBothInvFTup = procBothInvFTupG 1 {-# INLINE procBothInvFTup #-} procBoth2InvFTup = procBothInvFTupG 2 {-# INLINE procBoth2InvFTup #-} procBoth3InvFTup = procBothInvFTupG 3 {-# INLINE procBoth3InvFTup #-} procBoth4InvFTup = procBothInvFTupG 4 {-# INLINE procBoth4InvFTup #-} procBothInvFFTupG :: Int -> Factors -> Double -> Coeffs2 -> Array Int (Int8, Bool) -> Array Int (Int8, Bool) -> Array Int (Int8, Bool) -> Array Int (Int8, Bool) -> Array Int ([Int8], Bool) -> Array Int ([Int8], Int8) -> Array Int (Int8, FlowSound -> Sound8) -> Array Int (Int8, Bool) -> Array Int ([Int8], Bool) -> Array Int ([Int8], Bool) -> Array Int ([Int8], Bool) -> Array Int (Int8, [Int8]) -> Array Int (Char,Int8) -> Array Int (Int8,[Int8]) -> Array Int (Char, Bool) -> Array Int (Char, Bool) -> Array Int (Int8,Bool) -> (Double -> Double) -> FlowSound -> FuncRep2 ReadyForConstructionUkr Double Double procBothInvFFTupG n ff k coeffs = procB2InvFFTup ff k coeffs (case n of 1 -> SD.syllableDurationsD 2 -> SD.syllableDurationsD2 3 -> SD.syllableDurationsD3 4 -> SD.syllableDurationsD4) {-# INLINE procBothInvFFTupG #-} procBothInvFFTup = procBothInvFFTupG 1 {-# INLINE procBothInvFFTup #-} procBoth2InvFFTup = procBothInvFFTupG 2 {-# INLINE procBoth2InvFFTup #-} procBoth3InvFFTup = procBothInvFFTupG 3 {-# INLINE procBoth3InvFFTup #-} procBoth4InvFFTup = procBothInvFFTupG 4 {-# INLINE procBoth4InvFFTup #-} -------------------------