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
volumeMaximum :: (RealRing.C y) => Sig.T y -> y
volumeMaximum =
Sig.foldL max zero . rectify
volumeEuclidean :: (Algebraic.C y) => Sig.T y -> y
volumeEuclidean =
Algebraic.sqrt . volumeEuclideanSqr
volumeEuclideanSqr :: (Field.C y) => Sig.T y -> y
volumeEuclideanSqr =
average . Sig.map sqr
volumeSum :: (Field.C y, Absolute.C y) => Sig.T y -> y
volumeSum = average . rectify
volumeVectorMaximum :: (NormedMax.C y yv, Ord y) => Sig.T yv -> y
volumeVectorMaximum =
Sig.foldL max zero . Sig.map NormedMax.norm
volumeVectorEuclidean :: (Algebraic.C y, NormedEuc.C y yv) => Sig.T yv -> y
volumeVectorEuclidean =
Algebraic.sqrt . volumeVectorEuclideanSqr
volumeVectorEuclideanSqr :: (Field.C y, NormedEuc.Sqr y yv) => Sig.T yv -> y
volumeVectorEuclideanSqr =
average . Sig.map NormedEuc.normSqr
volumeVectorSum :: (NormedSum.C y yv, Field.C y) => Sig.T yv -> y
volumeVectorSum =
average . Sig.map NormedSum.norm
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)
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))
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))
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 (i1i01) zero ++ [f1])
fAll fs))
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)
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
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
histogramIntMap :: (RealField.C y) => y -> Sig.T y -> (Int, Sig.T Int)
histogramIntMap binsPerUnit =
histogramDiscreteIntMap . quantize binsPerUnit
quantize :: (RealRing.C y) => y -> Sig.T y -> Sig.T Int
quantize binsPerUnit = Sig.map (floor . (binsPerUnit*))
attachOne :: Sig.T i -> [(i,Int)]
attachOne = Sig.toList . Sig.map (\i -> (i,one))
meanValues :: RealField.C y => Sig.T y -> [(Int,y)]
meanValues = concatMap Ana.spread . Sig.toList . Sig.mapAdjacent (,)
directCurrentOffset :: Field.C y => Sig.T y -> y
directCurrentOffset = average
scalarProduct :: Ring.C y => Sig.T y -> Sig.T y -> y
scalarProduct xs ys =
Sig.sum (Sig.zipWith (*) xs ys)
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
firstMoment :: Field.C y => Sig.T y -> y
firstMoment xs =
scalarProduct (Sig.iterate (one+) zero) xs
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)
rectify :: Absolute.C y => Sig.T y -> Sig.T y
rectify = Sig.map abs
zeros :: (Ord y, Additive.C y) => Sig.T y -> Sig.T Bool
zeros =
Sig.mapAdjacent (/=) . Sig.map (>=zero)
flipFlopHysteresis :: (Ord y) =>
(y,y) -> Ana.BinaryLevel -> Sig.T y -> Sig.T Ana.BinaryLevel
flipFlopHysteresis bnds = Sig.scanL (Ana.flipFlopHysteresisStep bnds)
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