wigner-ville-accelerate-0.1.0.2: Wigner-ville transform using the Accelerate library

Copyright[2017] Rinat Stryungis
LicenseBSD3
MaintainerRinat Stryungis <lazybonesxp@gmail.com>
Stabilityexperimental
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Data.Array.Accelerate.Math.WindowFunc

Description

Creation of window for smoothing in frequency-domain in Pseudo-Wigner-Ville distribuition

Synopsis

Documentation

data WindowFunc Source #

Function of the window. Rect - Rectangle.

Constructors

Rect 
Sin 
Lanczos 
Hanning 
Hamming 
Bartlett 

Instances

Data WindowFunc Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WindowFunc -> c WindowFunc #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WindowFunc #

toConstr :: WindowFunc -> Constr #

dataTypeOf :: WindowFunc -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c WindowFunc) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WindowFunc) #

gmapT :: (forall b. Data b => b -> b) -> WindowFunc -> WindowFunc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WindowFunc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WindowFunc -> r #

gmapQ :: (forall d. Data d => d -> u) -> WindowFunc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WindowFunc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WindowFunc -> m WindowFunc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WindowFunc -> m WindowFunc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WindowFunc -> m WindowFunc #

Read WindowFunc Source # 
Show WindowFunc Source # 

makeWindow :: (RealFloat e, Fractional (Exp e), Floating (Exp e), IsFloating e, FromIntegral Int e, Ord e) => WindowFunc -> Acc (Scalar Int) -> Acc (Array DIM1 e) Source #

Creates new window (1D array of odd length) with length and window function. For example win1 = makeWindow Sin lentgh Where length has type Acc (Scalar Int)