emd-0.1.2.1: Empirical Mode Decomposition and Hilbert-Huang Transform

Copyright(c) Justin Le 2018
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Numeric.HHT

Contents

Description

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: emd-0.1.2.0

Synopsis

Documentation

hhtEmd :: forall v n a. (Vector v a, KnownNat n, RealFloat 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, KnownNat n, RealFloat a) => EMDOpts a -> Vector v (n + 1) a -> HHT v n a Source #

Directly compute the Hilbert-Huang transform of a given time series. Essentially is a composition of hhtEmd and emd. See hhtEmd for a more flexible version.

hhtSpectrum Source #

Arguments

:: (KnownNat n, Ord k, Num a) 
=> (a -> k)

binning function. takes rev/tick freq between 0 and 1.

-> HHT Vector 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.

marginal Source #

Arguments

:: (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. 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.

degreeOfStationarity Source #

Arguments

:: (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 

Degree of stationarity, as a function of frequency.

newtype HHT v n a Source #

A Hilbert-Huang Transform. An HHT v n a is a Hilbert-Huang transform of an n-item time series of items of type a represented using vector v.

Create using hht or hhtEmd.

Constructors

HHT 

Fields

data HHTLine v n a Source #

A Hilbert Trasnform of a given IMF, given as a "skeleton line".

Constructors

HHTLine 

Fields

  • hlMags :: !(Vector v n a)

    IMF HHT Magnitude as a time series

  • hlFreqs :: !(Vector v n a)

    IMF HHT instantaneous frequency as a time series (between 0 and 1)

Instances
Eq (v a) => Eq (HHTLine v n a) Source # 
Instance details

Defined in Numeric.HHT

Methods

(==) :: HHTLine v n a -> HHTLine v n a -> Bool #

(/=) :: HHTLine v n a -> HHTLine v n a -> Bool #

Ord (v a) => Ord (HHTLine v n a) Source # 
Instance details

Defined in Numeric.HHT

Methods

compare :: HHTLine v n a -> HHTLine v n a -> Ordering #

(<) :: HHTLine v n a -> HHTLine v n a -> Bool #

(<=) :: HHTLine v n a -> HHTLine v n a -> Bool #

(>) :: HHTLine v n a -> HHTLine v n a -> Bool #

(>=) :: HHTLine v n a -> HHTLine v n a -> Bool #

max :: HHTLine v n a -> HHTLine v n a -> HHTLine v n a #

min :: HHTLine v n a -> HHTLine v n a -> HHTLine v n a #

Show (v a) => Show (HHTLine v n a) Source # 
Instance details

Defined in Numeric.HHT

Methods

showsPrec :: Int -> HHTLine v n a -> ShowS #

show :: HHTLine v n a -> String #

showList :: [HHTLine v n a] -> ShowS #

data EMDOpts a Source #

Options for EMD composition.

Constructors

EO 

Fields

Instances
Eq a => Eq (EMDOpts a) Source # 
Instance details

Defined in Numeric.EMD

Methods

(==) :: EMDOpts a -> EMDOpts a -> Bool #

(/=) :: EMDOpts a -> EMDOpts a -> Bool #

Ord a => Ord (EMDOpts a) Source # 
Instance details

Defined in Numeric.EMD

Methods

compare :: EMDOpts a -> EMDOpts a -> Ordering #

(<) :: EMDOpts a -> EMDOpts a -> Bool #

(<=) :: EMDOpts a -> EMDOpts a -> Bool #

(>) :: EMDOpts a -> EMDOpts a -> Bool #

(>=) :: EMDOpts a -> EMDOpts a -> Bool #

max :: EMDOpts a -> EMDOpts a -> EMDOpts a #

min :: EMDOpts a -> EMDOpts a -> EMDOpts a #

Show a => Show (EMDOpts a) Source # 
Instance details

Defined in Numeric.EMD

Methods

showsPrec :: Int -> EMDOpts a -> ShowS #

show :: EMDOpts a -> String #

showList :: [EMDOpts a] -> ShowS #

data SiftCondition a Source #

Stop conditions for sifting process

Constructors

SCStdDev !a

Stop using standard SD method

SCTimes !Int

Stop after a fixed number of sifting iterations

SCOr (SiftCondition a) (SiftCondition a)

One or the other

SCAnd (SiftCondition a) (SiftCondition a)

Stop when both conditions are met

Instances
Eq a => Eq (SiftCondition a) Source # 
Instance details

Defined in Numeric.EMD

Ord a => Ord (SiftCondition a) Source # 
Instance details

Defined in Numeric.EMD

Show a => Show (SiftCondition a) Source # 
Instance details

Defined in Numeric.EMD

data SplineEnd a Source #

End condition for spline

Constructors

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: emd-0.1.2.0

Instances
Eq a => Eq (SplineEnd a) Source # 
Instance details

Defined in Numeric.EMD.Internal.Spline

Methods

(==) :: SplineEnd a -> SplineEnd a -> Bool #

(/=) :: SplineEnd a -> SplineEnd a -> Bool #

Ord a => Ord (SplineEnd a) Source # 
Instance details

Defined in Numeric.EMD.Internal.Spline

Show a => Show (SplineEnd a) Source # 
Instance details

Defined in Numeric.EMD.Internal.Spline

Hilbert transforms (internal usage)

hilbert :: forall v n a. (Vector v a, Vector v (Complex a), KnownNat n, Floating 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.

Numerically assumes that the signal is zero everywhere outside of the vector, instead of the periodic assumption taken by matlab's version.

hilbertIm :: forall v n a. (Vector v a, KnownNat n, Floating 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.

Numerically assumes that the signal is zero everywhere outside of the vector, instead of the periodic assumption taken by matlab's version.

hilbertMagFreq :: forall v n a. (Vector v a, KnownNat n, RealFloat a) => Vector v (n + 1) a -> (Vector v (n + 1) a, Vector v n 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.