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 (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.
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).
However, for convenience, Numeric.EMD.Unsized is provided with an unsafe unsized interface.
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 SiftCondition a
- = SCStdDev a
- | SCTimes Int
- | SCOr (SiftCondition a) (SiftCondition a)
- | SCAnd (SiftCondition a) (SiftCondition a)
- defaultSC :: Fractional a => SiftCondition a
- data SplineEnd
- 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 -> Bool -> Vector v (n + 1) a -> Maybe (Vector v (n + 1) a, Vector v (n + 1) a)
EMD (Hilbert-Huang Transform)
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 (Hilbert-Huang Transform) 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 a Hilbert-Huang transform 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 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 # | |
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 |
Instances
Eq SplineEnd Source # | |
Ord SplineEnd Source # | |
Show SplineEnd 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 iterations |
envelopes :: (Vector v a, KnownNat n, Fractional a, Ord a) => SplineEnd -> Bool -> 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.