{-# LANGUAGE FlexibleContexts #-}
{- |
In this module we demonstrate techniques for getting sound in real-time.
Getting real-time performance is mostly an issue of the right signal data structure.
However, there is no one-size-fits-all data structure.
For choosing the right one, you need to understand how various data structures work,
what are their strengths and what are their weaknesses.
-}
module Synthesizer.Generic.Tutorial
{-# DEPRECATED "do not import that module, it is only intended for demonstration" #-}
 where

import qualified Synthesizer.Plain.Tutorial as Tutorial -- needed for Haddock

import qualified Sound.Sox.Play as Play
import qualified Sound.Sox.Write as Write
import qualified Sound.Sox.Option.Format as SoxOpt
import qualified Synthesizer.Basic.Binary as BinSmp
import qualified Synthesizer.Storable.Signal as SigSt
import qualified Synthesizer.Generic.Signal as SigG
import qualified Synthesizer.State.Signal as Sig
import qualified Synthesizer.Causal.Process as Causal
import Control.Arrow ((&&&), (^<<), (<<^), (<<<), )

import qualified Synthesizer.Generic.Oscillator as Osci
import qualified Synthesizer.Generic.Piece as Piece
import qualified Synthesizer.Generic.Filter.NonRecursive as Filt
import qualified Synthesizer.Plain.Filter.Recursive as FiltRec
import qualified Synthesizer.Plain.Filter.Recursive.Universal as UniFilter
import qualified Synthesizer.Basic.Wave as Wave
import Synthesizer.Piecewise ((#|-), (-|#), (#|), (|#), )

import qualified Synthesizer.State.Control as CtrlS
import qualified Synthesizer.State.Oscillator as OsciS

import System.Exit (ExitCode, )
import NumericPrelude.Numeric
import NumericPrelude.Base
import Prelude ()


{- |
First, we define a play routine for lazy storable vectors.
Storable lazy vectors are lazy lists of low-level arrays.
They are both efficient in time and memory consumption,
but the blocks disallow feedback by small delays.
Elements of a storable vector must be of type class Storable.
This means that elements must have fixed size
and advanced data types like functions cannot be used.
-}
play :: SigSt.T Double -> IO ExitCode
play :: Vector Double -> IO ExitCode
play =
   forall y (sig :: * -> *).
C y =>
(Handle -> sig y -> IO ()) -> T -> Int -> sig y -> IO ExitCode
Play.simple forall a. Storable a => Handle -> Vector a -> IO ()
SigSt.hPut T
SoxOpt.none Int
44100 forall b c a. (b -> c) -> (a -> b) -> a -> c
.
   forall x y.
(Storable x, Storable y) =>
(x -> y) -> Vector x -> Vector y
SigSt.map Double -> Int16
BinSmp.int16FromDouble

{- |
Here is a simple oscillator generated as lazy storable vector.
An oscillator is a signal generator,
that is it produces a signal
without consuming other signals that correspond in time.
Signal generators have the maximal block size as parameter.
This is the lower limit of possible feedback delays.
-}
oscillator :: IO ExitCode
oscillator :: IO ExitCode
oscillator =
   Vector Double -> IO ExitCode
play (forall a (sig :: * -> *) b.
(C a, Write sig b) =>
LazySize -> T a b -> T a -> a -> sig b
Osci.static LazySize
SigG.defaultLazySize forall a. C a => T a a
Wave.sine forall a. C a => a
zero (Double
0.01::Double))


{- |
A routine just for the case that we want to post-process a signal somewhere else.
-}
write :: FilePath -> SigSt.T Double -> IO ExitCode
write :: FilePath -> Vector Double -> IO ExitCode
write FilePath
name =
   forall y (sig :: * -> *).
C y =>
(Handle -> sig y -> IO ())
-> T -> FilePath -> Int -> sig y -> IO ExitCode
Write.simple forall a. Storable a => Handle -> Vector a -> IO ()
SigSt.hPut T
SoxOpt.none FilePath
name Int
44100 forall b c a. (b -> c) -> (a -> b) -> a -> c
.
   forall x y.
(Storable x, Storable y) =>
(x -> y) -> Vector x -> Vector y
SigSt.map Double -> Int16
BinSmp.int16FromDouble

{- |
The simple brass sound demonstrates
how to generate piecewise defined curves.
Some infix operators are used in order to make the pieces fit in height.
There are also operators for intended jumps.
-}
brass :: IO ExitCode
brass :: IO ExitCode
brass =
--   write "brass.aiff" $
   Vector Double -> IO ExitCode
play forall a b. (a -> b) -> a -> b
$
   forall a (sig :: * -> *).
(C a, Transform sig a) =>
sig a -> sig a -> sig a
Filt.envelope
      (forall a (sig :: * -> *).
(C a, Transform (sig a)) =>
LazySize -> T a a (LazySize -> a -> sig a) -> sig a
Piece.run LazySize
SigG.defaultLazySize forall a b. (a -> b) -> a -> b
$
       Double
0    forall y t sig. y -> (PieceDist t y sig, T t y sig) -> T t y sig
|# ( Double
3000, forall a (sig :: * -> *). (C a, Write sig a) => a -> a -> T sig a
Piece.cubic Double
0.002 Double
0) forall t y sig.
(t, Piece t y sig)
-> (PieceRightSingle y, T t y sig)
-> (PieceDist t y sig, T t y sig)
#|-
       Double
0.7 forall y t sig.
y
-> (PieceDist t y sig, T t y sig)
-> (PieceRightSingle y, T t y sig)
-|# (Double
50000, forall (sig :: * -> *) a. Write sig a => T sig a
Piece.step) forall t y sig.
(t, Piece t y sig)
-> (PieceRightSingle y, T t y sig)
-> (PieceDist t y sig, T t y sig)
#|-
       Double
0.7 forall y t sig.
y
-> (PieceDist t y sig, T t y sig)
-> (PieceRightSingle y, T t y sig)
-|# (Double
10000, forall a (sig :: * -> *). (C a, Write sig a) => a -> T sig a
Piece.exponential Double
0) forall t y sig.
(t, Piece t y sig) -> y -> (PieceDist t y sig, T t y sig)
#| (Double
0.01::Double)) forall a b. (a -> b) -> a -> b
$
   forall (sig :: * -> *) y. Write sig y => LazySize -> T y -> sig y
SigG.fromState LazySize
SigG.defaultLazySize forall a b. (a -> b) -> a -> b
$
   forall a (sig :: * -> *).
(C a, Transform sig a) =>
a -> sig a -> sig a
Filt.amplify Double
0.5 forall a b. (a -> b) -> a -> b
$
   forall y (sig :: * -> *).
(C y, Transform sig y) =>
sig y -> sig y -> sig y
SigG.mix
      (forall a b. C a => T a b -> T a -> a -> T b
OsciS.static forall a. C a => T a a
Wave.saw forall a. C a => a
zero (Double
0.00499::Double))
      (forall a b. C a => T a b -> T a -> a -> T b
OsciS.static forall a. C a => T a a
Wave.saw forall a. C a => a
zero (Double
0.00501::Double))


{- |
We rewrite the filter example 'Tutorial.filterSaw'
in terms of type classes for more signal types.
The constraints become quite large
because we must assert, that a particular sample type
can be used in the addressed signal type.
-}
filterSawSig ::
   (SigG.Write sig Double,
    SigG.Transform sig (UniFilter.Result Double),
    SigG.Transform sig (UniFilter.Parameter Double)) =>
   sig Double
filterSawSig :: forall (sig :: * -> *).
(Write sig Double, Transform sig (Result Double),
 Transform sig (Parameter Double)) =>
sig Double
filterSawSig =
   forall (sig :: * -> *) y0 y1.
(Transform0 sig, Storage (sig y0), Storage (sig y1)) =>
(y0 -> y1) -> sig y0 -> sig y1
SigG.map forall a. Result a -> a
UniFilter.lowpass forall a b. (a -> b) -> a -> b
$ forall (sig :: * -> *) a b ctrl s.
(Transform sig a, Transform sig b, Read sig ctrl) =>
Simple s ctrl a b -> sig ctrl -> sig a -> sig b
SigG.modifyModulated forall a v.
(C a, C a v) =>
Simple (State v) (Parameter a) v (Result v)
UniFilter.modifier (forall (sig :: * -> *) y0 y1.
(Transform0 sig, Storage (sig y0), Storage (sig y1)) =>
(y0 -> y1) -> sig y0 -> sig y1
SigG.map (\Double
f -> forall a. C a => Pole a -> Parameter a
UniFilter.parameter forall a b. (a -> b) -> a -> b
$ forall a. a -> a -> Pole a
FiltRec.Pole Double
10 (Double
0.04forall a. C a => a -> a -> a
+Double
0.02forall a. C a => a -> a -> a
*Double
f)) forall a b. (a -> b) -> a -> b
$ forall a (sig :: * -> *) b.
(C a, Write sig b) =>
LazySize -> T a b -> T a -> a -> sig b
Osci.static LazySize
SigG.defaultLazySize forall a. C a => T a a
Wave.sine forall a. C a => a
zero (Double
0.00001::Double)) forall a b. (a -> b) -> a -> b
$ forall a (sig :: * -> *) b.
(C a, Write sig b) =>
LazySize -> T a b -> T a -> a -> sig b
Osci.static LazySize
SigG.defaultLazySize forall a. C a => T a a
Wave.saw forall a. C a => a
zero (Double
0.002::Double)

{- |
Here we instantiate 'filterSawSig' for storable vectors and play it.
This means that all operations convert a storable vector into another storable vector.
While every single operation probably is as efficient as possible,
the composition of all those processes could be more efficient.
So keep on reading.
-}
filterSaw :: IO ExitCode
filterSaw :: IO ExitCode
filterSaw =
   Vector Double -> IO ExitCode
play forall (sig :: * -> *).
(Write sig Double, Transform sig (Result Double),
 Transform sig (Parameter Double)) =>
sig Double
filterSawSig


{- |
The next signal type we want to consider is the stateful signal generator.
It is not a common data structure, where the sample values are materialized.
Instead it is a description of how to generate sample values iteratively.
This is almost identical to the @Data.Stream@ module from the @stream-fusion@ package.
With respect to laziness and restrictions of the sample type (namely none),
this signal representation is equivalent to lists.
You can convert one into the other in a lossless way.
That is, function as sample type is possible.
Combination of such signal generators is easily possible
and does not require temporary storage,
because this signal representation needs no sample value storage at all.
However at the end of such processes, the signal must be materialized.
Here we write the result into a lazy storable vector and play that.
What the compiler actually does is to create a single loop,
that generates the storable vector to be played in one go.
-}
playState :: Sig.T Double -> IO ExitCode
playState :: T Double -> IO ExitCode
playState =
   forall y (sig :: * -> *).
C y =>
(Handle -> sig y -> IO ()) -> T -> Int -> sig y -> IO ExitCode
Play.simple forall a. Storable a => Handle -> Vector a -> IO ()
SigSt.hPut T
SoxOpt.none Int
44100 forall b c a. (b -> c) -> (a -> b) -> a -> c
.
   forall (sig :: * -> *) y. Write sig y => LazySize -> T y -> sig y
SigG.fromState LazySize
SigG.defaultLazySize forall b c a. (b -> c) -> (a -> b) -> a -> c
.
   forall a b. (a -> b) -> T a -> T b
Sig.map Double -> Int16
BinSmp.int16FromDouble

{- |
We demonstrate the stateful signal generator using the known 'filterSaw' example.
Actually we can reuse the code from above,
because the signal generator is also an instance of the generic signal class.
-}
filterSawState :: IO ExitCode
filterSawState :: IO ExitCode
filterSawState =
   T Double -> IO ExitCode
playState forall (sig :: * -> *).
(Write sig Double, Transform sig (Result Double),
 Transform sig (Parameter Double)) =>
sig Double
filterSawSig


{- |
Merging subsequent signal processes based on signal generators
into an efficient large signal processor is easy.
Not storing intermediate results is however a problem in another situation:
Sometimes you want to share one signal between several processes.
-}
filterPingStateProc :: Sig.T Double -> Sig.T Double
filterPingStateProc :: T Double -> T Double
filterPingStateProc T Double
env =
   forall a (sig :: * -> *).
(C a, Transform sig a) =>
sig a -> sig a -> sig a
Filt.envelope T Double
env forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> T a -> T b
Sig.map forall a. Result a -> a
UniFilter.lowpass forall a b. (a -> b) -> a -> b
$ forall s ctrl a b. Simple s ctrl a b -> T ctrl -> T a -> T b
Sig.modifyModulated forall a v.
(C a, C a v) =>
Simple (State v) (Parameter a) v (Result v)
UniFilter.modifier (forall a b. (a -> b) -> T a -> T b
Sig.map (\Double
f -> forall a. C a => Pole a -> Parameter a
UniFilter.parameter forall a b. (a -> b) -> a -> b
$ forall a. a -> a -> Pole a
FiltRec.Pole Double
10 (Double
0.03forall a. C a => a -> a -> a
*Double
f)) forall a b. (a -> b) -> a -> b
$ T Double
env) forall a b. (a -> b) -> a -> b
$ forall a b. C a => T a b -> T a -> a -> T b
OsciS.static forall a. C a => T a a
Wave.saw forall a. C a => a
zero (Double
0.002::Double)

{- |
In the following example we generate an exponential curve
which shall be used both as envelope
and as resonance frequency control of a resonant lowpass.
Actually, recomputing an exponential curve is not an issue,
since it only needs one multiplication per sample.
But it is simple enough to demonstrate the problem and its solutions.
The expression @let env = exponential2 50000 1@ fools the reader of the program,
since the @env@ that is shared, is only the signal generator,
that is, the description of how to compute the exponential curve successively.
That is wherever a signal process reads @env@, it is computed again.
-}
filterPingState :: IO ExitCode
filterPingState :: IO ExitCode
filterPingState =
   T Double -> IO ExitCode
playState forall a b. (a -> b) -> a -> b
$
   T Double -> T Double
filterPingStateProc forall a b. (a -> b) -> a -> b
$
   forall a. C a => a -> a -> T a
CtrlS.exponential2 Double
50000 Double
1

{- |
You can achieve sharing by a very simple way.
You can write the result of the signal generator in a list ('Sig.toList')
and use this list as source for a new generator ('Sig.fromList').
'Sig.fromList' provides a signal generator that generates new sample values
by delivering the next sample from the list.

In a real world implementation you would move
the @Sig.fromList . Sig.toList@ to 'filterPingStateProc',
since the caller cannot know, that this function uses the signal twice,
and the implementor of 'filterPingStateProc' cannot know,
how expensive the computation of @env@ is.

You can use any other signal type for sharing, e.g. storable vectors,
but whatever type you choose, you also get its disadvantages.
Namely, storable vectors only work for storable samples
and lists are generally slow,
and they also cannot be optimized away,
since this only works, when no sharing is required.

Whenever a signal is shared as input between several signal processes,
the actual materialized data is that
between the slowest and the fastest reading process.
This is due to lazy evaluation and garbage collection.
If the different readers read with different speed,
then you will certainly need a temporary sample storage.
-}
filterPingShare :: IO ExitCode
filterPingShare :: IO ExitCode
filterPingShare =
   T Double -> IO ExitCode
playState forall a b. (a -> b) -> a -> b
$
   T Double -> T Double
filterPingStateProc forall a b. (a -> b) -> a -> b
$
   forall y. [y] -> T y
Sig.fromList forall a b. (a -> b) -> a -> b
$ forall y. T y -> [y]
Sig.toList forall a b. (a -> b) -> a -> b
$ forall a. C a => a -> a -> T a
CtrlS.exponential2 Double
50000 Double
1

{- |
It is however not uncommon that all readers read with the same speed.
In this case we would in principle only need to share the input signal per sample.
This way we would not need a data structure
for storing a sub-sequence of samples temporarily.
But how to do that practically?

The solution is not to think in terms of signals and signal processors,
e.g. @Sig.T a@ and @Sig.T a -> Sig.T b -> Sig.T c@, respectively,
but in terms of signal processors, that are guaranteed to run in sync.
That is we must assert that signal processors
process the samples in chronological order and emit one sample per input sample.
We call such processes \"causal\" processes.
For example @Causal.T (a,b) c@ represents the function @Sig.T (a,b) -> Sig.T c@
but it also carries the guarantee,
that for each input of type @(a,b)@
one sample of type @c@ is emitted or the output terminates.
Internally it is the Kleisli arrow of the @StateT Maybe@ monad.

Another important application of the Causal arrow is feedback.
Using causal processes guarantees, that a process cannot read ahead,
such that it runs into future data, which does still not exist due to recursion.

Programming with arrows needs a bit experience or Haskell extensions.
Haskell extensions are either an @Arrow@ syntax preprocessor
or the preprocessor that is built into GHC.
However, for computing with physical dimensions
you can no longer use the original @Arrow@ class
and thus you cannot use the arrow syntax.
So here is an example of how to program 'filterPingShare'
using @Arrow@ combinators.
-}
filterPingCausal :: IO ExitCode
filterPingCausal :: IO ExitCode
filterPingCausal =
   T Double -> IO ExitCode
playState forall a b. (a -> b) -> a -> b
$
   let proc :: T Double Double
proc =
          forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a. C a => a -> a -> a
(*) forall (a :: * -> * -> *) c d b.
Arrow a =>
(c -> d) -> a b c -> a b d
^<<
          ((forall a. Result a -> a
UniFilter.lowpass forall (a :: * -> * -> *) c d b.
Arrow a =>
(c -> d) -> a b c -> a b d
^<<
            forall a v. (C a, C a v) => T (Parameter a, v) (Result v)
UniFilter.causal forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
<<<
            forall (sig :: * -> *) a b. Read sig a => sig a -> T b (b, a)
Causal.feedSnd (forall a b. C a => T a b -> T a -> a -> T b
OsciS.static forall a. C a => T a a
Wave.saw forall a. C a => a
zero (Double
0.002::Double)) forall (a :: * -> * -> *) c d b.
Arrow a =>
a c d -> (b -> c) -> a b d
<<^
            (\Double
f -> forall a. C a => Pole a -> Parameter a
UniFilter.parameter forall a b. (a -> b) -> a -> b
$ forall a. a -> a -> Pole a
FiltRec.Pole Double
10 (Double
0.03forall a. C a => a -> a -> a
*Double
f)))
           forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&&
           forall a. T a a
Causal.id)
   in  forall (sig :: * -> *) a b.
(Transform sig a, Transform sig b) =>
T a b -> sig a -> sig b
Causal.apply T Double Double
proc forall a b. (a -> b) -> a -> b
$ forall a. C a => a -> a -> T a
CtrlS.exponential2 Double
50000 Double
1