emd-0.1.3.0: Empirical Mode Decomposition and Hilbert-Huang Transform

Copyright(c) Justin Le 2018
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Numeric.HHT

Contents

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

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 #

Directly compute the Hilbert-Huang transform of a given time series. Essentially is a composition of hhtEmd and emd. See hhtEmd for a more flexible version.

hhtSpectrum 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.

marginal Source #

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.

degreeOfStationarity Source #

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.

newtype HHT v n a Source #

A Hilbert-Huang Transform. An HHT v n a is a Hilbert-Huang transform of an n-item time series of items of type a represented using vector v.

Create using hht or hhtEmd.

Constructors

HHT 

Fields

Instances
Eq (v a) => Eq (HHT v n a) Source # 
Instance details

Defined in Numeric.HHT

Methods

(==) :: HHT v n a -> HHT v n a -> Bool #

(/=) :: HHT v n a -> HHT v n a -> Bool #

Ord (v a) => Ord (HHT v n a) Source # 
Instance details

Defined in Numeric.HHT

Methods

compare :: HHT v n a -> HHT v n a -> Ordering #

(<) :: HHT v n a -> HHT v n a -> Bool #

(<=) :: HHT v n a -> HHT v n a -> Bool #

(>) :: HHT v n a -> HHT v n a -> Bool #

(>=) :: HHT v n a -> HHT v n a -> Bool #

max :: HHT v n a -> HHT v n a -> HHT v n a #

min :: HHT v n a -> HHT v n a -> HHT v n a #

Show (v a) => Show (HHT v n a) Source # 
Instance details

Defined in Numeric.HHT

Methods

showsPrec :: Int -> HHT v n a -> ShowS #

show :: HHT v n a -> String #

showList :: [HHT v n a] -> ShowS #

Generic (HHT v n a) Source # 
Instance details

Defined in Numeric.HHT

Associated Types

type Rep (HHT v n a) :: * -> * #

Methods

from :: HHT v n a -> Rep (HHT v n a) x #

to :: Rep (HHT v n a) x -> HHT v n a #

(Vector v a, KnownNat n, Binary (v a)) => Binary (HHT v n a) Source # 
Instance details

Defined in Numeric.HHT

Methods

put :: HHT v n a -> Put #

get :: Get (HHT v n a) #

putList :: [HHT v n a] -> Put #

type Rep (HHT v n a) Source # 
Instance details

Defined in Numeric.HHT

type Rep (HHT v n a) = D1 (MetaData "HHT" "Numeric.HHT" "emd-0.1.3.0-8B9GLcXbOZ06FyHsmMMhXM" True) (C1 (MetaCons "HHT" PrefixI True) (S1 (MetaSel (Just "hhtLines") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [HHTLine v n a])))

data HHTLine v n a Source #

A Hilbert Trasnform of a given IMF, given as a "skeleton line".

Constructors

HHTLine 

Fields

  • hlMags :: !(Vector v n a)

    IMF HHT Magnitude as a time series

  • hlFreqs :: !(Vector v n a)

    IMF HHT instantaneous frequency as a time series (between 0 and 1)

Instances
Eq (v a) => Eq (HHTLine v n a) Source # 
Instance details

Defined in Numeric.HHT

Methods

(==) :: HHTLine v n a -> HHTLine v n a -> Bool #

(/=) :: HHTLine v n a -> HHTLine v n a -> Bool #

Ord (v a) => Ord (HHTLine v n a) Source # 
Instance details

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 #

max :: HHTLine v n a -> HHTLine v n a -> HHTLine v n a #

min :: HHTLine v n a -> HHTLine v n a -> HHTLine v n a #

Show (v a) => Show (HHTLine v n a) Source # 
Instance details

Defined in Numeric.HHT

Methods

showsPrec :: Int -> HHTLine v n a -> ShowS #

show :: HHTLine v n a -> String #

showList :: [HHTLine v n a] -> ShowS #

Generic (HHTLine v n a) Source # 
Instance details

Defined in Numeric.HHT

Associated Types

type Rep (HHTLine v n a) :: * -> * #

Methods

from :: HHTLine v n a -> Rep (HHTLine v n a) x #

to :: Rep (HHTLine v n a) x -> HHTLine v n a #

(Vector v a, KnownNat n, Binary (v a)) => Binary (HHTLine v n a) Source # 
Instance details

Defined in Numeric.HHT

Methods

put :: HHTLine v n a -> Put #

get :: Get (HHTLine v n a) #

putList :: [HHTLine v n a] -> Put #

type Rep (HHTLine v n a) Source # 
Instance details

Defined in Numeric.HHT

type Rep (HHTLine v n a) = D1 (MetaData "HHTLine" "Numeric.HHT" "emd-0.1.3.0-8B9GLcXbOZ06FyHsmMMhXM" False) (C1 (MetaCons "HHTLine" PrefixI True) (S1 (MetaSel (Just "hlMags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Vector v n a)) :*: S1 (MetaSel (Just "hlFreqs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Vector v n a))))

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 #

Generic (EMDOpts a) Source # 
Instance details

Defined in Numeric.EMD

Associated Types

type Rep (EMDOpts a) :: * -> * #

Methods

from :: EMDOpts a -> Rep (EMDOpts a) x #

to :: Rep (EMDOpts a) x -> EMDOpts a #

Binary a => Binary (EMDOpts a) Source # 
Instance details

Defined in Numeric.EMD

Methods

put :: EMDOpts a -> Put #

get :: Get (EMDOpts a) #

putList :: [EMDOpts a] -> Put #

Fractional a => Default (EMDOpts a) Source # 
Instance details

Defined in Numeric.EMD

Methods

def :: EMDOpts a #

type Rep (EMDOpts a) Source # 
Instance details

Defined in Numeric.EMD

type Rep (EMDOpts a) = D1 (MetaData "EMDOpts" "Numeric.EMD" "emd-0.1.3.0-8B9GLcXbOZ06FyHsmMMhXM" 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 #

Constructors

BHClamp

Clamp envelope at end points (Matlab implementation)

BHSymmetric

Extend boundaries symmetrically

Instances
Eq BoundaryHandler Source # 
Instance details

Defined in Numeric.EMD

Ord BoundaryHandler Source # 
Instance details

Defined in Numeric.EMD

Show BoundaryHandler Source # 
Instance details

Defined in Numeric.EMD

Generic BoundaryHandler Source # 
Instance details

Defined in Numeric.EMD

Associated Types

type Rep BoundaryHandler :: * -> * #

Binary BoundaryHandler Source # 
Instance details

Defined in Numeric.EMD

type Rep BoundaryHandler Source # 
Instance details

Defined in Numeric.EMD

type Rep BoundaryHandler = D1 (MetaData "BoundaryHandler" "Numeric.EMD" "emd-0.1.3.0-8B9GLcXbOZ06FyHsmMMhXM" False) (C1 (MetaCons "BHClamp" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "BHSymmetric" PrefixI False) (U1 :: * -> *))

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

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

Generic (SiftCondition a) Source # 
Instance details

Defined in Numeric.EMD

Associated Types

type Rep (SiftCondition a) :: * -> * #

Binary a => Binary (SiftCondition a) Source # 
Instance details

Defined in Numeric.EMD

Fractional a => Default (SiftCondition a) Source # 
Instance details

Defined in Numeric.EMD

Methods

def :: SiftCondition a #

type Rep (SiftCondition a) Source # 
Instance details

Defined in Numeric.EMD

data SplineEnd a Source #

End condition for spline

Constructors

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 # 
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

Generic (SplineEnd a) Source # 
Instance details

Defined in Numeric.EMD.Internal.Spline

Associated Types

type Rep (SplineEnd a) :: * -> * #

Methods

from :: SplineEnd a -> Rep (SplineEnd a) x #

to :: Rep (SplineEnd a) x -> SplineEnd a #

Binary a => Binary (SplineEnd a) Source # 
Instance details

Defined in Numeric.EMD.Internal.Spline

Methods

put :: SplineEnd a -> Put #

get :: Get (SplineEnd a) #

putList :: [SplineEnd a] -> Put #

type Rep (SplineEnd a) Source # 
Instance details

Defined in Numeric.EMD.Internal.Spline

type Rep (SplineEnd a) = D1 (MetaData "SplineEnd" "Numeric.EMD.Internal.Spline" "emd-0.1.3.0-8B9GLcXbOZ06FyHsmMMhXM" 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))))

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.