emd-0.1.0.0: Empirical Mode Decomposition (Hilbert-Huang Transform)

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

Numeric.EMD

Contents

Description

Empirical Mode Decomposition (Hilbert-Huang Transform) in pure Haskell.

Main interface is emd, with defaultEO. A tracing version that outputs a log to stdout is also available, as emdTrace. This can be used to help track down a specific IMF that might be taking more time than desired.

Synopsis

EMD (Hilbert-Huang Transform)

emd :: (Vector v a, KnownNat n, Fractional a, Ord a) => EMDOpts a -> Vector v (n + 2) a -> EMD v (n + 2) a Source #

EMD decomposition (Hilbert-Huang Transform) of a given time series with a given sifting stop condition.

emdTrace :: (Vector v a, KnownNat n, Fractional a, Ord a, MonadIO m) => EMDOpts a -> Vector v (n + 2) a -> m (EMD v (n + 2) a) Source #

emd, but tracing results to stdout as IMFs are found. Useful for debugging to see how long each step is taking.

emd' :: (Vector v a, KnownNat n, Fractional a, Ord a, Applicative m) => (SiftResult v (n + 2) a -> m r) -> EMDOpts a -> Vector v (n + 2) a -> m (EMD v (n + 2) a) Source #

emd with a callback for each found IMF.

data EMD v n a Source #

An EMD v n a is a Hilbert-Huang transform of a time series with n items of type a stored in a vector v.

Constructors

EMD 

Fields

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

Defined in Numeric.EMD

Methods

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

show :: EMD v n a -> String #

showList :: [EMD 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 iterations

SCOr (SiftCondition a) (SiftCondition a)

one or the other

SCAnd (SiftCondition a) (SiftCondition a)

both conditions 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

Internal

sift :: (Vector v a, KnownNat n, Fractional a, Ord a) => EMDOpts a -> Vector v (n + 2) a -> SiftResult v (n + 2) a Source #

Iterated sifting process, used to produce either an IMF or a residual.

data SiftResult v n a Source #

The result of a sifting operation. Each sift either yields a residual, or a new IMF.

Constructors

SRResidual !(Vector v n a) 
SRIMF !(Vector v n a) !Int 

envelopes :: (Vector v a, KnownNat n, Fractional a, Ord a) => SplineEnd -> Bool -> Vector v (n + 2) a -> Maybe (Vector v (n + 2) a, Vector v (n + 2) a) Source #

Returns cubic splines of local minimums and maximums. Returns Nothing if there are not enough local minimum or maximums to create the splines.