emd-0.1.2.0: Empirical Mode Decomposition and 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 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.

This package uses "sized vectors" as its main interface, to ensure:

  1. The resulting EMD contains IMFs that are all the same length as the input vector
  2. We provide a vector of size of at least one.

There are many functions to convert unsized vectors to sized vectors in Data.Vector.Sized and associated modules, including toSized (for when you know the size at compile-time) and withSized (for when you don't).

Synopsis

Empirical Mode Decomposition

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

EMD decomposition of a given time series with a given sifting stop condition.

Takes a sized vector to ensure that:

  1. The resulting EMD contains IMFs that are all the same length as the input vector
  2. We provide a vector of size of at least one.

emdTrace :: (Vector v a, KnownNat n, Fractional a, Ord a, MonadIO m) => EMDOpts a -> Vector v (n + 1) a -> m (EMD v (n + 1) 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 + 1) a -> m r) -> EMDOpts a -> Vector v (n + 1) a -> m (EMD v (n + 1) a) Source #

emd with a callback for each found IMF.

data EMD v n a Source #

An EMD v n a is an Empirical Mode Decomposition 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 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 
SENatural 
SEClamped a a 
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

Internal

sift :: (Vector v a, KnownNat n, Fractional a, Ord a) => EMDOpts a -> Vector v (n + 1) a -> SiftResult v (n + 1) 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

number of sifting iterations

envelopes :: (Vector v a, KnownNat n, Fractional a, Ord a) => SplineEnd a -> Maybe BoundaryHandler -> Vector v (n + 1) a -> Maybe (Vector v (n + 1) a, Vector v (n + 1) 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.