Copyright | (c) Justin Le 2019 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Hilbert-Huang transform in pure Haskell.
The main data type is HHT
, which can be generated using hht
or
hhtEmd
. See Numeric.EMD for information on why this module uses
"sized vectors", and how to convert unsized vectors to sized vectors.
Since: 0.1.2.0
Synopsis
- data HHT v n a = HHT {
- hhtLines :: [HHTLine v n a]
- hhtResidual :: Vector v (n + 1) a
- data HHTLine v n a = HHTLine {}
- hhtEmd :: forall v n a. (Vector v a, Vector v (Complex a), KnownNat n, FFTWReal a) => EMD v (n + 1) a -> HHT v n a
- hht :: forall v n a. (Vector v a, Vector v (Complex a), KnownNat n, FFTWReal a) => EMDOpts v (n + 1) a -> Vector v (n + 1) a -> HHT v n a
- ihhtEmd :: (Vector v a, Floating a) => HHT v n a -> EMD v (n + 1) a
- ihht :: (Vector v a, Floating a) => HHT v n a -> Vector v (n + 1) a
- hhtSpectrum :: forall v n a k. (Vector v a, KnownNat n, Ord k, Num a) => (a -> k) -> HHT v n a -> Vector n (Map k a)
- hhtSparseSpectrum :: forall v n a k. (Vector v a, KnownNat n, Ord k, Num a) => (a -> k) -> HHT v n a -> Map (Finite n, k) a
- hhtDenseSpectrum :: forall v n m a. (Vector v a, KnownNat n, KnownNat m, Num a) => (a -> Finite m) -> HHT v n a -> Vector n (Vector m a)
- meanMarginal :: forall v n a k. (Vector v a, KnownNat n, Ord k, Fractional a) => (a -> k) -> HHT v n a -> Map k a
- marginal :: forall v n a k. (Vector v a, KnownNat n, Ord k, Num a) => (a -> k) -> HHT v n a -> Map k a
- instantaneousEnergy :: forall v n a. (Vector v a, KnownNat n, Num a) => HHT v n a -> Vector v n a
- degreeOfStationarity :: forall v n a k. (Vector v a, KnownNat n, Ord k, Fractional a, Eq a) => (a -> k) -> HHT v n a -> Map k a
- expectedFreq :: forall v n a. (Vector v a, KnownNat n, Fractional a) => HHT v n a -> Vector v n a
- dominantFreq :: forall v n a. (Vector v a, KnownNat n, Ord a) => HHT v n a -> Vector v n a
- foldFreq :: forall v u n a b c. (Vector v a, Vector u c, KnownNat n, Monoid b) => (a -> a -> b) -> (b -> c) -> HHT v n a -> Vector u n c
- data EMDOpts v n a = EO {
- eoSifter :: Sifter v n a
- eoSplineEnd :: SplineEnd a
- eoBoundaryHandler :: Maybe BoundaryHandler
- defaultEO :: (Vector v a, Fractional a, Ord a) => EMDOpts v n a
- data BoundaryHandler
- defaultSifter :: (Vector v a, Fractional a, Ord a) => Sifter v n a
- data SplineEnd a
- = SENotAKnot
- | SENatural
- | SEClamped a a
- hilbert :: forall v n a. (Vector v a, Vector v (Complex a), KnownNat n, FFTWReal a) => Vector v n a -> Vector v n (Complex a)
- hilbertIm :: forall v n a. (Vector v a, Vector v (Complex a), KnownNat n, FFTWReal a) => Vector v n a -> Vector v n a
- hilbertPolar :: forall v n a. (Vector v a, Vector v (Complex a), KnownNat n, FFTWReal a) => Vector v (n + 1) a -> (Vector v (n + 1) a, Vector v (n + 1) a)
- hilbertMagFreq :: forall v n a. (Vector v a, Vector v (Complex a), KnownNat n, FFTWReal a) => Vector v (n + 1) a -> (Vector v (n + 1) a, (Vector v n a, a))
Hilbert-Huang Transform
A Hilbert-Huang Transform. An
is a Hilbert-Huang
transform of an HHT
v n an
-item time series of items of type a
represented
using vector v
.
HHT | |
|
Instances
(Eq a, Eq (v a)) => Eq (HHT v n a) Source # | |
(Ord a, Ord (v a)) => Ord (HHT v n a) Source # | |
Defined in Numeric.HHT | |
(Show a, Show (v a)) => Show (HHT v n a) Source # | |
Generic (HHT v n a) Source # | |
(Vector v a, KnownNat n, Binary (v a), Binary a) => Binary (HHT v n a) Source # | Since: 0.1.3.0 |
(NFData (v a), NFData a) => NFData (HHT v n a) Source # | Since: 0.1.5.0 |
Defined in Numeric.HHT | |
type Rep (HHT v n a) Source # | |
Defined in Numeric.HHT type Rep (HHT v n a) = D1 (MetaData "HHT" "Numeric.HHT" "emd-0.2.0.0-inplace" False) (C1 (MetaCons "HHT" PrefixI True) (S1 (MetaSel (Just "hhtLines") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [HHTLine v n a]) :*: S1 (MetaSel (Just "hhtResidual") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector v (n + 1) a)))) |
A Hilbert Trasnform of a given IMF, given as a "skeleton line".
HHTLine | |
|
Instances
hhtEmd :: forall v n a. (Vector v a, Vector v (Complex a), KnownNat n, FFTWReal a) => EMD v (n + 1) a -> HHT v n a Source #
Compute the Hilbert-Huang transform from a given Empirical Mode Decomposition.
hht :: forall v n a. (Vector v a, Vector v (Complex a), KnownNat n, FFTWReal a) => EMDOpts v (n + 1) a -> Vector v (n + 1) a -> HHT v n a Source #
ihhtEmd :: (Vector v a, Floating a) => HHT v n a -> EMD v (n + 1) a Source #
Invert a Hilbert-Huang transform back to an Empirical Mode Decomposition
Since: 0.1.9.0
ihht :: (Vector v a, Floating a) => HHT v n a -> Vector v (n + 1) a Source #
Construct a time series correpsonding to its hilbert-huang transform.
Since: 0.1.9.0
Hilbert-Huang Spectrum
:: (Vector v a, KnownNat n, Ord k, Num a) | |
=> (a -> k) | binning function. takes rev/tick freq between 0 and 1. |
-> HHT v n a | |
-> Vector n (Map k a) |
Compute the full Hilbert-Huang Transform spectrum. At each timestep is a sparse map of frequency components and their respective magnitudes. Frequencies not in the map are considered to be zero.
Takes a "binning" function to allow you to specify how specific you want your frequencies to be.
See hhtSparseSpectrum
for a sparser version, and hhtDenseSpectrum
for a denser version.
:: (Vector v a, KnownNat n, Ord k, Num a) | |
=> (a -> k) | binning function. takes rev/tick freq between 0 and 1. |
-> HHT v n a | |
-> Map (Finite n, k) a |
A sparser vesion of hhtSpectrum
. Compute the full Hilbert-Huang
Transform spectrum. Returns a sparse matrix representing the power at
each time step (the
) and frequency (the Finite
nk
).
Takes a "binning" function to allow you to specify how specific you want your frequencies to be.
Since: 0.1.4.0
:: (Vector v a, KnownNat n, KnownNat m, Num a) | |
=> (a -> Finite m) | binning function. takes rev/tick freq between 0 and 1. |
-> HHT v n a | |
-> Vector n (Vector m a) |
A denser version of hhtSpectrum
. Compute the full Hilbert-Huang
Transform spectrum, returning a dense matrix (as a vector of vectors)
representing the power at each time step and each frequency.
Takes a "binning" function that maps a frequency to one of m
discrete
slots, for accumulation in the dense matrix.
Since: 0.1.4.0
Properties of spectrum
:: (Vector v a, KnownNat n, Ord k, Fractional a) | |
=> (a -> k) | binning function. takes rev/tick freq between 0 and 1. |
-> HHT v n a | |
-> Map k a |
Compute the mean marginal spectrum given a Hilbert-Huang Transform. It is similar to a Fourier Transform; it provides the "total power" over the entire time series for each frequency component, averaged over the length of the time series.
A binning function is accepted to allow you to specify how specific you want your frequencies to be.
Since: 0.1.8.0
:: (Vector v a, KnownNat n, Ord k, Num a) | |
=> (a -> k) | binning function. takes rev/tick freq between 0 and 1. |
-> HHT v n a | |
-> Map k a |
Compute the marginal spectrum given a Hilbert-Huang Transform. It
provides the "total power" over the entire time series for each
frequency component. See meanMarginal
for a version that averages
over the length of the time series, making it more close in nature to
the purpose of a Fourier Transform.
A binning function is accepted to allow you to specify how specific you want your frequencies to be.
instantaneousEnergy :: forall v n a. (Vector v a, KnownNat n, Num a) => HHT v n a -> Vector v n a Source #
Compute the instantaneous energy of the time series at every step via the Hilbert-Huang Transform.
:: (Vector v a, KnownNat n, Ord k, Fractional a, Eq a) | |
=> (a -> k) | binning function. takes rev/tick freq between 0 and 1. |
-> HHT v n a | |
-> Map k a |
Degree of stationarity, as a function of frequency.
expectedFreq :: forall v n a. (Vector v a, KnownNat n, Fractional a) => HHT v n a -> Vector v n a Source #
Returns the "expected value" of frequency at each time step, calculated as a weighted average of all contributions at every frequency at that time step.
Since: 0.1.4.0
dominantFreq :: forall v n a. (Vector v a, KnownNat n, Ord a) => HHT v n a -> Vector v n a Source #
Returns the dominant frequency (frequency with largest magnitude contribution) at each time step.
Since: 0.1.4.0
:: (Vector v a, Vector u c, KnownNat n, Monoid b) | |
=> (a -> a -> b) | Combining function, taking frequency, then magnitude |
-> (b -> c) | Projecting function |
-> HHT v n a | |
-> Vector u n c |
Fold and collapse a Hilbert-Huang transform along the frequency axis at each step in time along some monoid.
Since: 0.1.8.0
Options
Options for EMD composition.
EO | |
|
Instances
Generic (EMDOpts v n a) Source # | |
(Vector v a, Fractional a, Ord a) => Default (EMDOpts v n a) Source # | Since: 0.1.3.0 |
Defined in Numeric.EMD | |
type Rep (EMDOpts v n a) Source # | |
Defined in Numeric.EMD.Internal type Rep (EMDOpts v n a) = D1 (MetaData "EMDOpts" "Numeric.EMD.Internal" "emd-0.2.0.0-inplace" False) (C1 (MetaCons "EO" PrefixI True) (S1 (MetaSel (Just "eoSifter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Sifter v n a)) :*: (S1 (MetaSel (Just "eoSplineEnd") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SplineEnd a)) :*: S1 (MetaSel (Just "eoBoundaryHandler") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe BoundaryHandler))))) |
data BoundaryHandler Source #
Boundary conditions for splines.
BHClamp | Clamp envelope at end points (Matlab implementation) |
BHSymmetric | Extend boundaries symmetrically |
Instances
defaultSifter :: (Vector v a, Fractional a, Ord a) => Sifter v n a Source #
Default Sifter
defaultSifter =siftStdDev
0.3siftOr
siftTimes
50
R package uses
, Matlab uses no limitsiftTimes
20
End condition for spline
SENotAKnot | "Not-a-knot" condition: third derivatives are continuous at endpoints. Default for matlab spline. |
SENatural | "Natural" condition: curve becomes a straight line at endpoints. |
SEClamped a a | "Clamped" condition: Slope of curves at endpoints are explicitly given. Since: 0.1.2.0 |
Instances
Eq a => Eq (SplineEnd a) Source # | |
Ord a => Ord (SplineEnd a) Source # | |
Defined in Numeric.EMD.Internal.Spline | |
Show a => Show (SplineEnd a) Source # | |
Generic (SplineEnd a) Source # | |
Binary a => Binary (SplineEnd a) Source # | Since: 0.1.3.0 |
type Rep (SplineEnd a) Source # | |
Defined in Numeric.EMD.Internal.Spline type Rep (SplineEnd a) = D1 (MetaData "SplineEnd" "Numeric.EMD.Internal.Spline" "emd-0.2.0.0-inplace" False) (C1 (MetaCons "SENotAKnot" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SENatural" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SEClamped" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))) |
Hilbert transforms (internal usage)
hilbert :: forall v n a. (Vector v a, Vector v (Complex a), KnownNat n, FFTWReal a) => Vector v n a -> Vector v n (Complex a) Source #
Real part is original series and imaginary part is hilbert transformed series. Creates a "helical" form of the original series that rotates along the complex plane.
Note that since 0.1.7.0, this uses the same algorithm as the matlab implementation https://www.mathworks.com/help/signal/ref/hilbert.html
hilbertIm :: forall v n a. (Vector v a, Vector v (Complex a), KnownNat n, FFTWReal a) => Vector v n a -> Vector v n a Source #
Hilbert transformed series. Essentially the same series, but
phase-shifted 90 degrees. Is so-named because it is the "imaginary
part" of the proper hilbert transform, hilbert
.
Note that since 0.1.7.0, this uses the same algorithm as the matlab implementation https://www.mathworks.com/help/signal/ref/hilbert.html
hilbertPolar :: forall v n a. (Vector v a, Vector v (Complex a), KnownNat n, FFTWReal a) => Vector v (n + 1) a -> (Vector v (n + 1) a, Vector v (n + 1) a) Source #
The polar form of hilbert
: returns the magnitude and phase of the
discrete hilbert transform of a series.
The computation of magnitude is unique, but computing phase gives us some ambiguity. The interpretation of the hilbert transform for instantaneous frequency is that the original series "spirals" around the complex plane as time progresses, like a helix. So, we impose a constraint on the phase to uniquely determine it: \(\phi_{t+1}\) is the minimal valid phase such that \(\phi_{t+1} \geq \phi_{t}\). This enforces the phase to be monotonically increasing at the slowest possible detectable rate.
Since: 0.1.6.0
hilbertMagFreq :: forall v n a. (Vector v a, Vector v (Complex a), KnownNat n, FFTWReal a) => Vector v (n + 1) a -> (Vector v (n + 1) a, (Vector v n a, a)) Source #
Given a time series, return a time series of the magnitude of the hilbert transform and the frequency of the hilbert transform, in units of revolutions per tick. Is only expected to taken in proper/legal IMFs.
The frequency will always be between 0 and 1, since we can't determine anything faster given the discretization, and we exclude negative values as physically unmeaningful for an IMF.