{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE CPP, BangPatterns #-}
module Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2CommonOld 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 Phonetic.Languages.Array.Ukrainian.Common
import Languages.Rhythmicity
import Languages.Rhythmicity.Factor
import Melodics.Ukrainian.ArrInt8 (Sound8,FlowSound)
import Languages.Phonetic.Ukrainian.Syllable.ArrInt8
import Data.Maybe (isNothing)
import Text.Read (readMaybe)
import GHC.Arr
import GHC.Int
#ifdef __GLASGOW_HASKELL__
#if __GLASGOW_HASKELL__==708
/* code that applies only to GHC 7.8.* */
mconcat = concat
#endif
#endif
rhythmicityGH :: ([[[Sound8]]] -> [[Double]]) -> ([[Double]] -> Double) -> String -> Double
rhythmicityGH :: ([[[Sound8]]] -> [[Double]])
-> ([[Double]] -> Double) -> String -> Double
rhythmicityGH [[[Sound8]]] -> [[Double]]
f [[Double]] -> Double
g String
xs
| String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
xs = Double
0.0
| Bool
otherwise = [[Double]] -> Double
g ([[Double]] -> Double)
-> (String -> [[Double]]) -> String -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[Sound8]]] -> [[Double]]
f ([[[Sound8]]] -> [[Double]])
-> (String -> [[[Sound8]]]) -> String -> [[Double]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [[[Sound8]]]
createSyllablesUkrS (String -> Double) -> String -> Double
forall a b. (a -> b) -> a -> b
$ String
xs
{-# INLINE rhythmicityGH #-}