{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
module Synthesizer.State.Analysis (
volumeMaximum,
volumeEuclidean,
volumeEuclideanSqr,
volumeSum,
volumeVectorMaximum,
volumeVectorEuclidean,
volumeVectorEuclideanSqr,
volumeVectorSum,
bounds,
histogramDiscreteArray,
histogramLinearArray,
histogramDiscreteIntMap,
histogramLinearIntMap,
histogramIntMap,
directCurrentOffset,
scalarProduct,
centroid,
centroidRecompute,
firstMoment,
average,
averageRecompute,
rectify,
zeros,
flipFlopHysteresis,
chirpTransform,
) where
import qualified Synthesizer.Plain.Analysis as Ana
import qualified Synthesizer.State.Control as Ctrl
import qualified Synthesizer.State.Signal as Sig
import qualified Algebra.Algebraic as Algebraic
import qualified Algebra.RealField as RealField
import qualified Algebra.Field as Field
import qualified Algebra.RealRing as RealRing
import qualified Algebra.Absolute as Absolute
import qualified Algebra.Ring as Ring
import qualified Algebra.Additive as Additive
import qualified Algebra.NormedSpace.Maximum as NormedMax
import qualified Algebra.NormedSpace.Euclidean as NormedEuc
import qualified Algebra.NormedSpace.Sum as NormedSum
import qualified Data.IntMap as IntMap
import qualified Data.Array as Array
import Data.Array (accumArray)
import NumericPrelude.Numeric
import NumericPrelude.Base
{-# INLINE volumeMaximum #-}
volumeMaximum :: (RealRing.C y) => Sig.T y -> y
volumeMaximum =
Sig.foldL max zero . rectify
{-# INLINE volumeEuclidean #-}
volumeEuclidean :: (Algebraic.C y) => Sig.T y -> y
volumeEuclidean =
Algebraic.sqrt . volumeEuclideanSqr
{-# INLINE volumeEuclideanSqr #-}
volumeEuclideanSqr :: (Field.C y) => Sig.T y -> y
volumeEuclideanSqr =
average . Sig.map sqr
{-# INLINE volumeSum #-}
volumeSum :: (Field.C y, Absolute.C y) => Sig.T y -> y
volumeSum = average . rectify
{-# INLINE volumeVectorMaximum #-}
volumeVectorMaximum :: (NormedMax.C y yv, Ord y) => Sig.T yv -> y
volumeVectorMaximum =
Sig.foldL max zero . Sig.map NormedMax.norm
{-# INLINE volumeVectorEuclidean #-}
volumeVectorEuclidean :: (Algebraic.C y, NormedEuc.C y yv) => Sig.T yv -> y
volumeVectorEuclidean =
Algebraic.sqrt . volumeVectorEuclideanSqr
{-# INLINE volumeVectorEuclideanSqr #-}
volumeVectorEuclideanSqr :: (Field.C y, NormedEuc.Sqr y yv) => Sig.T yv -> y
volumeVectorEuclideanSqr =
average . Sig.map NormedEuc.normSqr
{-# INLINE volumeVectorSum #-}
volumeVectorSum :: (NormedSum.C y yv, Field.C y) => Sig.T yv -> y
volumeVectorSum =
average . Sig.map NormedSum.norm
{-# INLINE bounds #-}
bounds :: (Ord y) => Sig.T y -> (y,y)
bounds =
Sig.switchL
(error "Analysis.bounds: List must contain at least one element.")
(\x xs ->
Sig.foldL (\(minX,maxX) y -> (min y minX, max y maxX)) (x,x) xs)
{-# INLINE histogramDiscreteArray #-}
histogramDiscreteArray :: Sig.T Int -> (Int, Sig.T Int)
histogramDiscreteArray =
withAtLeast1 "histogramDiscreteArray" $ \ x ->
let hist =
accumArray (+) zero
(bounds x) (attachOne x)
in (fst (Array.bounds hist), Sig.fromList (Array.elems hist))
{-# INLINE histogramLinearArray #-}
histogramLinearArray :: RealField.C y => Sig.T y -> (Int, Sig.T y)
histogramLinearArray =
withAtLeast2 "histogramLinearArray" $ \ x ->
let (xMin,xMax) = bounds x
hist =
accumArray (+) zero
(floor xMin, floor xMax)
(meanValues x)
in (fst (Array.bounds hist), Sig.fromList (Array.elems hist))
{-# INLINE histogramDiscreteIntMap #-}
histogramDiscreteIntMap :: Sig.T Int -> (Int, Sig.T Int)
histogramDiscreteIntMap =
withAtLeast1 "histogramDiscreteIntMap" $ \ x ->
let hist = IntMap.fromListWith (+) (attachOne x)
in case IntMap.toAscList hist of
[] -> error "histogramDiscreteIntMap: the list was non-empty before processing ..."
fAll@((fIndex,fHead):fs) -> (fIndex,
Sig.fromList $
fHead :
concat (zipWith
(\(i0,_) (i1,f1) -> replicate (i1-i0-1) zero ++ [f1])
fAll fs))
{-# INLINE histogramLinearIntMap #-}
histogramLinearIntMap :: RealField.C y => Sig.T y -> (Int, Sig.T y)
histogramLinearIntMap =
withAtLeast2 "histogramLinearIntMap" $ \ x ->
let hist = IntMap.fromListWith (+) (meanValues x)
(startKey:_, elems) = unzip (IntMap.toAscList hist)
in (startKey, Sig.fromList elems)
{-# INLINE withAtLeast1 #-}
withAtLeast1 ::
String ->
(Sig.T y -> (Int, Sig.T y)) ->
Sig.T y ->
(Int, Sig.T y)
withAtLeast1 name f x =
maybe
(error (name ++ ": no bounds found"), Sig.empty)
(const (f x)) $
Sig.viewL x
{-# INLINE withAtLeast2 #-}
withAtLeast2 :: (RealRing.C y) =>
String ->
(Sig.T y -> (Int, Sig.T y)) ->
Sig.T y ->
(Int, Sig.T y)
withAtLeast2 name f x =
maybe
(error (name ++ ": no bounds found"), Sig.empty)
(\(y,ys) ->
if Sig.null ys
then (floor y, Sig.empty)
else f x) $
Sig.viewL x
{-# INLINE histogramIntMap #-}
histogramIntMap :: (RealField.C y) => y -> Sig.T y -> (Int, Sig.T Int)
histogramIntMap binsPerUnit =
histogramDiscreteIntMap . quantize binsPerUnit
{-# INLINE quantize #-}
quantize :: (RealRing.C y) => y -> Sig.T y -> Sig.T Int
quantize binsPerUnit = Sig.map (floor . (binsPerUnit*))
{-# INLINE attachOne #-}
attachOne :: Sig.T i -> [(i,Int)]
attachOne = Sig.toList . Sig.map (\i -> (i,one))
{-# INLINE meanValues #-}
meanValues :: RealField.C y => Sig.T y -> [(Int,y)]
meanValues = concatMap Ana.spread . Sig.toList . Sig.mapAdjacent (,)
{-# INLINE directCurrentOffset #-}
directCurrentOffset :: Field.C y => Sig.T y -> y
directCurrentOffset = average
{-# INLINE scalarProduct #-}
scalarProduct :: Ring.C y => Sig.T y -> Sig.T y -> y
scalarProduct xs ys =
Sig.sum (Sig.zipWith (*) xs ys)
{-# INLINE centroid #-}
centroid :: Field.C y => Sig.T y -> y
centroid =
uncurry (/) .
Sig.sum .
Sig.zipWith
(\k x -> (k*x, x))
(Sig.iterate (one+) zero)
centroidRecompute :: Field.C y => Sig.T y -> y
centroidRecompute xs =
firstMoment xs / Sig.sum xs
{-# INLINE firstMoment #-}
firstMoment :: Field.C y => Sig.T y -> y
firstMoment xs =
scalarProduct (Sig.iterate (one+) zero) xs
{-# INLINE average #-}
average :: Field.C y => Sig.T y -> y
average =
uncurry (/) .
Sig.sum .
Sig.map (flip (,) one)
averageRecompute :: Field.C y => Sig.T y -> y
averageRecompute x =
Sig.sum x / fromIntegral (Sig.length x)
{-# INLINE rectify #-}
rectify :: Absolute.C y => Sig.T y -> Sig.T y
rectify = Sig.map abs
{-# INLINE zeros #-}
zeros :: (Ord y, Additive.C y) => Sig.T y -> Sig.T Bool
zeros =
Sig.mapAdjacent (/=) . Sig.map (>=zero)
{-# INLINE flipFlopHysteresis #-}
flipFlopHysteresis :: (Ord y) =>
(y,y) -> Ana.BinaryLevel -> Sig.T y -> Sig.T Ana.BinaryLevel
flipFlopHysteresis bnds = Sig.scanL (Ana.flipFlopHysteresisStep bnds)
{-# INLINE chirpTransform #-}
chirpTransform :: Ring.C y =>
y -> Sig.T y -> Sig.T y
chirpTransform z xs =
Sig.map (scalarProduct xs) $
Sig.map (\zn -> Ctrl.curveMultiscaleNeutral (*) zn one) $
Ctrl.curveMultiscaleNeutral (*) z one