{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
module Synthesizer.Plain.Wave where

import qualified Synthesizer.Basic.Wave as Wave

import qualified Synthesizer.Plain.ToneModulation as ToneMod
import qualified Synthesizer.Plain.Interpolation  as Interpolation
import qualified Synthesizer.Plain.Signal as Sig
import Data.Array ((!), listArray)

import qualified Algebra.RealField             as RealField

import NumericPrelude.Numeric

import NumericPrelude.Base


sample :: (RealField.C a) =>
   Interpolation.T a v -> Sig.T v -> Wave.T a v
sample ip wave =
   let len = length wave
       arr = listArray (0, pred len) wave
   in  Wave.fromFunction $ \ phase ->
           let (n,q) = splitFraction (phase * fromIntegral len)
               xs = map (arr!) (map (flip mod len)
                      (enumFrom (n - Interpolation.offset ip)))
--                map (arr!) (enumFromTo (n - Interpolation.offset ip)) ++ cycle wave
           in  Interpolation.func ip q xs

{- |
We assume that a tone was generated by a shape modulated oscillator.
We try to reconstruct the wave function
(with parameters shape control and phase)
from a tone by interpolation.

The unit for the shape control parameter is the sampling period.
That is the shape parameter is a time parameter
pointing to a momentary shape of the prototype signal.
Of course this momentary shape does not exist
and we can only guess it using interpolation.

At the boundaries we repeat the outermost shapes
that can be reconstructed entirely from interpolated data
(that is, no extrapolation is needed).
This way we cannot reproduce the shape at the boundaries
because we have no data for cyclically extending it.
On the other hand this method guarantees a nice wave shape
with the required fractional period.

It must be
   @length tone >=
       Interpolation.number ipStep +
       Interpolation.number ipLeap * ceiling period@.
-}
sampledTone :: (RealField.C a) =>
   Interpolation.T a v ->
   Interpolation.T a v ->
   a -> Sig.T v -> a -> Wave.T a v
sampledTone ipLeap ipStep period tone shape = Wave.Cons $ \phase ->
   uncurry (ToneMod.interpolateCell ipLeap ipStep) $
   ToneMod.sampledToneCell
      (ToneMod.makePrototype
          (Interpolation.margin ipLeap) (Interpolation.margin ipStep)
          (round period) period tone)
      shape phase
{-
*Synthesizer.Basic.Wave>
GNUPlot.plotFunc [] (GNUPlot.linearScale 1000 (0,12)) (\t -> sampledTone Interpolation.linear Interpolation.linear (6::Double) ([-5,-3,-1,1,3,5,-4,-4,-4,4,4,4]++replicate 20 0) t (t/6))

*Synthesizer.Plain.Oscillator>
let period = 6.3::Double in GNUPlot.plotFunc [] (GNUPlot.linearScale 1000 (-10,20)) (\t -> Wave.sampledTone Interpolation.linear Interpolation.cubic period (take 20 $ staticSine 0 (1/period)) t (t/period))
-}