Copyright | (c) Justin Le 2018 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Numeric.EMD
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:
- 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
.
Constructors
EMD | |
Fields
|
Options for EMD composition.
Constructors
EO | |
Fields
|
Instances
Eq a => Eq (EMDOpts a) Source # | |
Ord a => Ord (EMDOpts a) Source # | |
Show a => Show (EMDOpts a) Source # | |
data BoundaryHandler Source #
Constructors
BHClamp | Clamp envelope at end points (Matlab implementation) |
BHSymmetric | Extend boundaries symmetrically |
Instances
Eq BoundaryHandler Source # | |
Defined in Numeric.EMD Methods (==) :: BoundaryHandler -> BoundaryHandler -> Bool # (/=) :: BoundaryHandler -> BoundaryHandler -> Bool # | |
Ord BoundaryHandler Source # | |
Defined in Numeric.EMD Methods compare :: BoundaryHandler -> BoundaryHandler -> Ordering # (<) :: BoundaryHandler -> BoundaryHandler -> Bool # (<=) :: BoundaryHandler -> BoundaryHandler -> Bool # (>) :: BoundaryHandler -> BoundaryHandler -> Bool # (>=) :: BoundaryHandler -> BoundaryHandler -> Bool # max :: BoundaryHandler -> BoundaryHandler -> BoundaryHandler # min :: BoundaryHandler -> BoundaryHandler -> BoundaryHandler # | |
Show BoundaryHandler Source # | |
Defined in Numeric.EMD Methods showsPrec :: Int -> BoundaryHandler -> ShowS # show :: BoundaryHandler -> String # showList :: [BoundaryHandler] -> 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 # | |
Defined in Numeric.EMD Methods (==) :: SiftCondition a -> SiftCondition a -> Bool # (/=) :: SiftCondition a -> SiftCondition a -> Bool # | |
Ord a => Ord (SiftCondition a) Source # | |
Defined in Numeric.EMD Methods compare :: SiftCondition a -> SiftCondition a -> Ordering # (<) :: SiftCondition a -> SiftCondition a -> Bool # (<=) :: SiftCondition a -> SiftCondition a -> Bool # (>) :: SiftCondition a -> SiftCondition a -> Bool # (>=) :: SiftCondition a -> SiftCondition a -> Bool # max :: SiftCondition a -> SiftCondition a -> SiftCondition a # min :: SiftCondition a -> SiftCondition a -> SiftCondition a # | |
Show a => Show (SiftCondition a) Source # | |
Defined in Numeric.EMD Methods showsPrec :: Int -> SiftCondition a -> ShowS # show :: SiftCondition a -> String # showList :: [SiftCondition a] -> ShowS # |
defaultSC :: Fractional a => SiftCondition a Source #
Default SiftCondition
End condition for spline
Constructors
SENotAKnot | |
SENatural | |
SEClamped a a |
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 # | |
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.