{-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Phonetic.Languages.Array.Ukrainian.PropertiesFuncRepG21Old -- Copyright : (c) OleksandrZhabenko 2020-2022 -- 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. Instead of vectors, uses arrays. module Phonetic.Languages.Array.Ukrainian.PropertiesFuncRepG21Old ( -- ** Usual ones procBothF , procBothFF , procBothInvF , procBothInvFF ) where import Phonetic.Languages.Array.Ukrainian.Common import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2CommonOld import Phonetic.Languages.Array.Ukrainian.PropertiesFuncRepG2CommonOld import Phonetic.Languages.Basis import qualified Languages.Phonetic.Ukrainian.Syllable.Double.ArrInt8 as SD import Melodics.Ukrainian.ArrInt8 import GHC.Arr (Array) import GHC.Int (Int8) procBothF :: (Ord c) => (Double -> c) -> Coeffs2 -> FuncRep2 String Double c procBothF g coeffs = procB2F g SD.syllableDurationsD coeffs {-# INLINE procBothF #-} procBothFF :: (Ord c) => Double -> (Double -> c) -> Coeffs2 -> FuncRep2 String Double c procBothFF k g coeffs = procB2FF k g SD.syllableDurationsD coeffs {-# INLINE procBothFF #-} procBothInvF :: (Ord c) => (Double -> c) -> Coeffs2 -> FuncRep2 String Double c procBothInvF g coeffs = procB2InvF g SD.syllableDurationsD coeffs {-# INLINE procBothInvF #-} procBothInvFF :: (Ord c) => Double -> (Double -> c) -> Coeffs2 -> FuncRep2 String Double c procBothInvFF k g coeffs = procB2InvFF k g SD.syllableDurationsD coeffs {-# INLINE procBothInvFF #-}