{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE FlexibleContexts #-}
module Synthesizer.Plain.Effect.Fly where

import qualified Synthesizer.Causal.Spatial as Spatial
import qualified Synthesizer.Causal.Process as Causal

import qualified Synthesizer.Plain.Oscillator as Osci
import qualified Synthesizer.Plain.Filter.NonRecursive as FiltNR
import qualified Synthesizer.Plain.Interpolation as Interpolation

import qualified Synthesizer.Plain.File as File
import System.Exit(ExitCode)

import System.Random (randomRs, mkStdGen, )

import qualified Algebra.NormedSpace.Euclidean as Euc

import NumericPrelude.Numeric
import NumericPrelude.Base


{-
  ghc -O -fvia-C --make Fly.hs && echo start && time a.out
-}

main :: IO ExitCode
main :: IO ExitCode
main =
   forall a. C a => FilePath -> a -> [(a, a)] -> IO ExitCode
File.writeStereoToInt16 FilePath
"Fly" Double
sampleRate
      (forall a. Int -> [a] -> [a]
take (forall a b. (C a, C b) => a -> b
round (Double
10forall a. C a => a -> a -> a
*Double
sampleRate)) [(Double, Double)]
fly)

sampleRate :: Double
sampleRate :: Double
sampleRate = Double
44100

{- | stereo sound of a humming fly -}
fly :: [(Double,Double)]
fly :: [(Double, Double)]
fly =
   let pinkNoise :: Int -> Double -> y -> T y
pinkNoise Int
seed Double
freq y
range =
           forall t y. (C t, C t y) => t -> T t -> T y -> T y
Interpolation.multiRelativeZeroPadCubic (Double
0::Double)
           (forall a. a -> [a]
repeat (Double
freqforall a. C a => a -> a -> a
/Double
sampleRate))
           (forall a g. (Random a, RandomGen g) => (a, a) -> g -> [a]
randomRs (-y
range,y
range) (Int -> StdGen
mkStdGen Int
seed))
       {- the track of a fly is composed of a slow motion over a big range
          and fast but small oscillations -}
       flyCoord :: Int -> [c]
flyCoord Int
seed = forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith forall a. C a => a -> a -> a
(+) (forall {y}. (C Double y, Random y) => Int -> Double -> y -> T y
pinkNoise Int
seed Double
40 c
0.3)
                                   (forall {y}. (C Double y, Random y) => Int -> Double -> y -> T y
pinkNoise Int
seed  Double
1 c
10)
       {- explicit signature required
          because of multi-param type class NormedEuc -}
       trajectory :: [(Double, Double, Double)]
       trajectory :: [(Double, Double, Double)]
trajectory =
          forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 (forall {c}. (C Double c, Random c, C c) => Int -> [c]
flyCoord Int
366210)
               (forall {c}. (C Double c, Random c, C c) => Int -> [c]
flyCoord Int
234298)
               (forall {c}. (C Double c, Random c, C c) => Int -> [c]
flyCoord Int
654891)

       channel :: (Double, Double, Double) -> [Double]
channel (Double, Double, Double)
ear =
          let ([Double]
phase,[Double]
volumes) =
                 forall a b. [(a, b)] -> ([a], [b])
unzip forall a b. (a -> b) -> a -> b
$ forall (sig :: * -> *) a b.
(Transform sig a, Transform sig b) =>
T a b -> sig a -> sig b
Causal.apply (forall a v (arrow :: * -> * -> *).
(C a, C a v, Arrow arrow) =>
a -> a -> v -> arrow v (a, a)
Spatial.moveAround Double
1 Double
0.1 (Double, Double, Double)
ear) [(Double, Double, Double)]
trajectory
              -- (*sampleRate) in 'speed' and
              -- (/sampleRate) in 'freqs' neutralizes
              speeds :: [Double]
speeds  = forall a b. (a -> b) -> [a] -> [b]
map (\(Double, Double, Double)
v -> Double
250forall a. C a => a -> a -> a
/Double
sampleRate forall a. C a => a -> a -> a
+ Double
2 forall a. C a => a -> a -> a
* forall a v. C a v => v -> a
Euc.norm (Double, Double, Double)
v)
                            (forall v. C v => T v -> T v
FiltNR.differentiate [(Double, Double, Double)]
trajectory)
              freqs :: [Double]
freqs   = forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith forall a. C a => a -> a -> a
(+) [Double]
speeds (forall v. C v => T v -> T v
FiltNR.differentiate [Double]
phase)
              sound :: [Double]
sound   = forall a. C a => a -> T a -> T a
Osci.freqModSaw Double
0 [Double]
freqs
          in  forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith forall a. C a => a -> a -> a
(*) (forall a b. (a -> b) -> [a] -> [b]
map (Double
10forall a. C a => a -> a -> a
*) [Double]
volumes) [Double]
sound

   in  forall a b. [a] -> [b] -> [(a, b)]
zip ((Double, Double, Double) -> [Double]
channel (-Double
1,Double
0,Double
0)) ((Double, Double, Double) -> [Double]
channel (Double
1,Double
0,Double
0))