Copyright | (c) Justin Le 2018 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
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:
- The resulting
EMD
contains IMFs that are all the same length as the input vector - 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
- emd :: (Vector v a, KnownNat n, Fractional a, Ord a) => EMDOpts a -> Vector v (n + 1) a -> EMD v (n + 1) a
- 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)
- 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)
- data EMD v n a = EMD {
- emdIMFs :: ![Vector v n a]
- emdResidual :: !(Vector v n a)
- data EMDOpts a = EO {}
- defaultEO :: Fractional a => EMDOpts a
- data BoundaryHandler
- data SiftCondition a
- = SCStdDev !a
- | SCTimes !Int
- | SCOr (SiftCondition a) (SiftCondition a)
- | SCAnd (SiftCondition a) (SiftCondition a)
- defaultSC :: Fractional a => SiftCondition a
- data SplineEnd a
- = SENotAKnot
- | SENatural
- | SEClamped a a
- sift :: (Vector v a, KnownNat n, Fractional a, Ord a) => EMDOpts a -> Vector v (n + 1) a -> SiftResult v (n + 1) a
- data SiftResult v n a
- = SRResidual !(Vector v n a)
- | SRIMF !(Vector v n a) !Int
- 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)
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:
- The resulting
EMD
contains IMFs that are all the same length as the input vector - 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.
An
is an Empirical Mode Decomposition of a time series
with EMD
v n an
items of type a
stored in a vector v
.
The component-wise sum of emdIMFs
and emdResidual
should yield
exactly the original series.
EMD | |
|
Instances
Eq (v a) => Eq (EMD v n a) Source # | |
Ord (v a) => Ord (EMD v n a) Source # | |
Defined in Numeric.EMD | |
Show (v a) => Show (EMD v n a) Source # | |
Generic (EMD v n a) Source # | |
(Vector v a, KnownNat n, Binary (v a)) => Binary (EMD v n a) Source # | Since: emd-0.1.3.0 |
type Rep (EMD v n a) Source # | |
Defined in Numeric.EMD type Rep (EMD v n a) = D1 (MetaData "EMD" "Numeric.EMD" "emd-0.1.4.0-H6PjqqQcZoREuq6F4k90ku" False) (C1 (MetaCons "EMD" PrefixI True) (S1 (MetaSel (Just "emdIMFs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Vector v n a]) :*: S1 (MetaSel (Just "emdResidual") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Vector v n a)))) |
Options for EMD composition.
EO | |
|
Instances
Eq a => Eq (EMDOpts a) Source # | |
Ord a => Ord (EMDOpts a) Source # | |
Defined in Numeric.EMD | |
Show a => Show (EMDOpts a) Source # | |
Generic (EMDOpts a) Source # | |
Binary a => Binary (EMDOpts a) Source # | Since: emd-0.1.3.0 |
Fractional a => Default (EMDOpts a) Source # | Since: emd-0.1.3.0 |
Defined in Numeric.EMD | |
type Rep (EMDOpts a) Source # | |
Defined in Numeric.EMD type Rep (EMDOpts a) = D1 (MetaData "EMDOpts" "Numeric.EMD" "emd-0.1.4.0-H6PjqqQcZoREuq6F4k90ku" False) (C1 (MetaCons "EO" PrefixI True) (S1 (MetaSel (Just "eoSiftCondition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SiftCondition a)) :*: (S1 (MetaSel (Just "eoSplineEnd") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SplineEnd a)) :*: S1 (MetaSel (Just "eoBoundaryHandler") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe BoundaryHandler))))) |
data BoundaryHandler Source #
BHClamp | Clamp envelope at end points (Matlab implementation) |
BHSymmetric | Extend boundaries symmetrically |
Instances
data SiftCondition a Source #
Stop conditions for sifting process
Data type is lazy in its fields, so this infinite data type:
nTimes n = SCTimes n SCOr
nTimes (n + 1)
will be treated identically as:
nTimes = SCTimes
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
defaultSC :: Fractional a => SiftCondition a Source #
Default SiftCondition
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: emd-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: emd-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.1.4.0-H6PjqqQcZoREuq6F4k90ku" False) (C1 (MetaCons "SENotAKnot" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "SENatural" PrefixI False) (U1 :: * -> *) :+: 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)))) |
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.
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.