{-# OPTIONS_HADDOCK show-extensions #-}

-- |
-- Module      :  Phonetic.Languages.Array.Ukrainian.PropertiesFuncRepG23
-- Copyright   :  (c) OleksandrZhabenko 2020-2021
-- 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.PropertiesFuncRepG23 (
  -- * Functions with 'Double'
  -- ** NEW Working with generated by r-glpk-phonetic-languages-ukrainian-durations syllable durations
  procBoth3F
  , procBoth3FF
  , procBoth3InvF
  , procBoth3InvFF
  -- ** With tuples
  , procBoth3FTup
  , procBoth3FFTup
  , procBoth3InvFTup
  , procBoth3InvFFTup
) where

import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2Common
import Phonetic.Languages.Array.Ukrainian.PropertiesFuncRepG2Common
import Phonetic.Languages.Simplified.DataG.Base
import qualified Languages.Phonetic.Ukrainian.Syllable.Double.ArrInt8 as SD
import Melodics.Ukrainian.ArrInt8
import GHC.Arr (Array)
import GHC.Int (Int8)

procBoth3F
  :: (Ord c) => (Double -> c)
  -> Coeffs2
  -> FuncRep2 String Double c
procBoth3F :: (Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth3F Double -> c
g Coeffs2
coeffs  = (Double -> c)
-> ([[[Sound8]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c)
-> ([[[Sound8]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2F Double -> c
g [[[Sound8]]] -> [[Double]]
SD.syllableDurationsD3 Coeffs2
coeffs
{-# INLINE procBoth3F #-}

procBoth3InvF
  :: (Ord c) => (Double -> c)
  -> Coeffs2
  -> FuncRep2 String Double c
procBoth3InvF :: (Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth3InvF Double -> c
g Coeffs2
coeffs  = (Double -> c)
-> ([[[Sound8]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c)
-> ([[[Sound8]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2InvF Double -> c
g [[[Sound8]]] -> [[Double]]
SD.syllableDurationsD3 Coeffs2
coeffs
{-# INLINE procBoth3InvF #-}

procBoth3FF
  :: (Ord c) => Double
  -> (Double -> c)
  -> Coeffs2
  -> FuncRep2 String Double c
procBoth3FF :: Double -> (Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth3FF Double
k Double -> c
g Coeffs2
coeffs  = Double
-> (Double -> c)
-> ([[[Sound8]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
Double
-> (Double -> c)
-> ([[[Sound8]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2FF Double
k Double -> c
g [[[Sound8]]] -> [[Double]]
SD.syllableDurationsD3 Coeffs2
coeffs
{-# INLINE procBoth3FF #-}

procBoth3InvFF
  :: (Ord c) => Double
  -> (Double -> c)
  -> Coeffs2
  -> FuncRep2 String Double c
procBoth3InvFF :: Double -> (Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth3InvFF Double
k Double -> c
g Coeffs2
coeffs  = Double
-> (Double -> c)
-> ([[[Sound8]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
Double
-> (Double -> c)
-> ([[[Sound8]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2InvFF Double
k Double -> c
g [[[Sound8]]] -> [[Double]]
SD.syllableDurationsD3 Coeffs2
coeffs
{-# INLINE procBoth3InvFF #-}

-----------------------------------------------

procBoth3FTup
  :: (Ord c) => 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 -> c)
  -> Coeffs2
  -> FuncRep2 String Double c
procBoth3FTup :: Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> (Double -> c)
-> Coeffs2
-> FuncRep2 String Double c
procBoth3FTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double -> c
g Coeffs2
coeffs
 = Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> (Double -> c)
-> ([[[Sound8]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> (Double -> c)
-> ([[[Sound8]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2FTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double -> c
g [[[Sound8]]] -> [[Double]]
SD.syllableDurationsD3 Coeffs2
coeffs
{-# INLINE procBoth3FTup #-}

procBoth3FFTup
  :: (Ord c) => 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 -> c)
  -> Coeffs2
  -> FuncRep2 String Double c
procBoth3FFTup :: Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> Double
-> (Double -> c)
-> Coeffs2
-> FuncRep2 String Double c
procBoth3FFTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double
k Double -> c
g Coeffs2
coeffs
 = Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> Double
-> (Double -> c)
-> ([[[Sound8]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> Double
-> (Double -> c)
-> ([[[Sound8]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2FFTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double
k Double -> c
g [[[Sound8]]] -> [[Double]]
SD.syllableDurationsD3 Coeffs2
coeffs
{-# INLINE procBoth3FFTup #-}

procBoth3InvFTup
  :: (Ord c) => 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 -> c)
  -> Coeffs2
  -> FuncRep2 String Double c
procBoth3InvFTup :: Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> (Double -> c)
-> Coeffs2
-> FuncRep2 String Double c
procBoth3InvFTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double -> c
g Coeffs2
coeffs
 = Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> (Double -> c)
-> ([[[Sound8]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> (Double -> c)
-> ([[[Sound8]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2InvFTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double -> c
g [[[Sound8]]] -> [[Double]]
SD.syllableDurationsD3 Coeffs2
coeffs
{-# INLINE procBoth3InvFTup #-}

procBoth3InvFFTup
  :: (Ord c) => 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 -> c)
  -> Coeffs2
  -> FuncRep2 String Double c
procBoth3InvFFTup :: Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> Double
-> (Double -> c)
-> Coeffs2
-> FuncRep2 String Double c
procBoth3InvFFTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double
k Double -> c
g Coeffs2
coeffs
 = Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> Double
-> (Double -> c)
-> ([[[Sound8]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> Double
-> (Double -> c)
-> ([[[Sound8]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2InvFFTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double
k Double -> c
g [[[Sound8]]] -> [[Double]]
SD.syllableDurationsD3 Coeffs2
coeffs
{-# INLINE procBoth3InvFFTup #-}