{-# LANGUAGE NoImplicitPrelude #-} module Synthesizer.Plain.Miscellaneous where import qualified Algebra.NormedSpace.Euclidean as Euc import qualified Algebra.Field as Field -- import qualified Algebra.Ring as Ring -- import qualified Algebra.Additive as Additive import qualified Prelude as P import NumericPrelude.Base import NumericPrelude.Numeric {- * Spatial effects -} {-| simulate an moving sounding object convert the way of the object through 3D space into a delay and attenuation information, sonicDelay is the reciprocal of the sonic velocity -} receive3Dsound :: (Field.C a, Euc.C a v) => a -> a -> v -> [v] -> ([a],[a]) receive3Dsound att sonicDelay ear way = let dists = map (Euc.norm) (map (subtract ear) way) phase = map (sonicDelay*) dists volumes = map (\x -> 1/(att+x)^2) dists in (phase, volumes)