Copyright | (c) Justin Le 2018 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Numeric.HHT
Description
Hilbert-Huang transform in pure Haskell.
The main data type is HHT
, which can be generated using hht
or
hhtEmd
. See Numeric.EMD for information on why this module uses
"sized vectors", and how to convert unsized vectors to sized vectors.
Since: emd-0.1.2.0
Synopsis
- hhtEmd :: forall v n a. (Vector v a, KnownNat n, RealFloat a) => EMD v (n + 1) a -> HHT v n a
- hht :: forall v n a. (Vector v a, KnownNat n, RealFloat a) => EMDOpts a -> Vector v (n + 1) a -> HHT v n a
- hhtSpectrum :: forall n a k. (KnownNat n, Ord k, Num a) => (a -> k) -> HHT Vector n a -> Vector n (Map k a)
- marginal :: forall v n a k. (Vector v a, KnownNat n, Ord k, Num a) => (a -> k) -> HHT v n a -> Map k a
- instantaneousEnergy :: forall v n a. (Vector v a, KnownNat n, Num a) => HHT v n a -> Vector v n a
- degreeOfStationarity :: forall v n a k. (Vector v a, KnownNat n, Ord k, Fractional a) => (a -> k) -> HHT v n a -> Map k a
- newtype HHT v n a = HHT {}
- data HHTLine v n a = HHTLine {}
- 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
- hilbert :: forall v n a. (Vector v a, Vector v (Complex a), KnownNat n, Floating a) => Vector v n a -> Vector v n (Complex a)
- hilbertIm :: forall v n a. (Vector v a, KnownNat n, Floating a) => Vector v n a -> Vector v n a
- hilbertMagFreq :: forall v n a. (Vector v a, KnownNat n, RealFloat a) => Vector v (n + 1) a -> (Vector v (n + 1) a, Vector v n a)
Documentation
hhtEmd :: forall v n a. (Vector v a, KnownNat n, RealFloat a) => EMD v (n + 1) a -> HHT v n a Source #
Compute the Hilbert-Huang transform from a given Empirical Mode Decomposition.
hht :: forall v n a. (Vector v a, KnownNat n, RealFloat a) => EMDOpts a -> Vector v (n + 1) a -> HHT v n a Source #
Arguments
:: (KnownNat n, Ord k, Num a) | |
=> (a -> k) | binning function. takes rev/tick freq between 0 and 1. |
-> HHT Vector n a | |
-> Vector n (Map k a) |
Compute the full Hilbert-Huang Transform spectrum. At each timestep is a sparse map of frequency components and their respective magnitudes. Frequencies not in the map are considered to be zero.
Takes a "binning" function to allow you to specify how specific you want your frequencies to be.
Arguments
:: (Vector v a, KnownNat n, Ord k, Num a) | |
=> (a -> k) | binning function. takes rev/tick freq between 0 and 1. |
-> HHT v n a | |
-> Map k a |
Compute the marginal spectrum given a Hilbert-Huang Transform. A binning function is accepted to allow you to specify how specific you want your frequencies to be.
instantaneousEnergy :: forall v n a. (Vector v a, KnownNat n, Num a) => HHT v n a -> Vector v n a Source #
Compute the instantaneous energy of the time series at every step via the Hilbert-Huang Transform.
Arguments
:: (Vector v a, KnownNat n, Ord k, Fractional a) | |
=> (a -> k) | binning function. takes rev/tick freq between 0 and 1. |
-> HHT v n a | |
-> Map k a |
Degree of stationarity, as a function of frequency.
A Hilbert-Huang Transform. An
is a Hilbert-Huang
transform of an HHT
v n an
-item time series of items of type a
represented
using vector v
.
A Hilbert Trasnform of a given IMF, given as a "skeleton line".
Constructors
HHTLine | |
Instances
Eq (v a) => Eq (HHTLine v n a) Source # | |
Ord (v a) => Ord (HHTLine v n a) Source # | |
Defined in Numeric.HHT Methods compare :: HHTLine v n a -> HHTLine v n a -> Ordering # (<) :: HHTLine v n a -> HHTLine v n a -> Bool # (<=) :: HHTLine v n a -> HHTLine v n a -> Bool # (>) :: HHTLine v n a -> HHTLine v n a -> Bool # (>=) :: HHTLine v n a -> HHTLine v n a -> Bool # | |
Show (v a) => Show (HHTLine v n a) Source # | |
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 # | |
Hilbert transforms (internal usage)
hilbert :: forall v n a. (Vector v a, Vector v (Complex a), KnownNat n, Floating a) => Vector v n a -> Vector v n (Complex a) Source #
Real part is original series and imaginary part is hilbert transformed series. Creates a "helical" form of the original series that rotates along the complex plane.
Numerically assumes that the signal is zero everywhere outside of the vector, instead of the periodic assumption taken by matlab's version.
hilbertIm :: forall v n a. (Vector v a, KnownNat n, Floating a) => Vector v n a -> Vector v n a Source #
Hilbert transformed series. Essentially the same series, but
phase-shifted 90 degrees. Is so-named because it is the "imaginary
part" of the proper hilbert transform, hilbert
.
Numerically assumes that the signal is zero everywhere outside of the vector, instead of the periodic assumption taken by matlab's version.
hilbertMagFreq :: forall v n a. (Vector v a, KnownNat n, RealFloat a) => Vector v (n + 1) a -> (Vector v (n + 1) a, Vector v n a) Source #
Given a time series, return a time series of the magnitude of the hilbert transform and the frequency of the hilbert transform, in units of revolutions per tick. Is only expected to taken in proper/legal IMFs.
The frequency will always be between 0 and 1, since we can't determine anything faster given the discretization, and we exclude negative values as physically unmeaningful for an IMF.