{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module JSDOM.Generated.AudioProcessingEvent
       (getPlaybackTime, getInputBuffer, getOutputBuffer,
        AudioProcessingEvent(..), gTypeAudioProcessingEvent)
       where
import Prelude ((.), (==), (>>=), return, IO, Int, Float, Double, Bool(..), Maybe, maybe, fromIntegral, round, realToFrac, fmap, Show, Read, Eq, Ord, Maybe(..))
import qualified Prelude (error)
import Data.Typeable (Typeable)
import Data.Traversable (mapM)
import Language.Javascript.JSaddle (JSM(..), JSVal(..), JSString, strictEqual, toJSVal, valToStr, valToNumber, valToBool, js, jss, jsf, jsg, function, asyncFunction, new, array, jsUndefined, (!), (!!))
import Data.Int (Int64)
import Data.Word (Word, Word64)
import JSDOM.Types
import Control.Applicative ((<$>))
import Control.Monad (void)
import Control.Lens.Operators ((^.))
import JSDOM.EventTargetClosures (EventName, unsafeEventName, unsafeEventNameAsync)
import JSDOM.Enums
getPlaybackTime :: (MonadDOM m) => AudioProcessingEvent -> m Double
getPlaybackTime :: forall (m :: * -> *).
MonadDOM m =>
AudioProcessingEvent -> m Double
getPlaybackTime AudioProcessingEvent
self
  = DOM Double -> m Double
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((AudioProcessingEvent
self AudioProcessingEvent
-> Getting (JSM JSVal) AudioProcessingEvent (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String -> IndexPreservingGetter AudioProcessingEvent (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"playbackTime") JSM JSVal -> (JSVal -> DOM Double) -> DOM Double
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM Double
forall value. ToJSVal value => value -> DOM Double
valToNumber)
getInputBuffer ::
               (MonadDOM m) => AudioProcessingEvent -> m AudioBuffer
getInputBuffer :: forall (m :: * -> *).
MonadDOM m =>
AudioProcessingEvent -> m AudioBuffer
getInputBuffer AudioProcessingEvent
self
  = DOM AudioBuffer -> m AudioBuffer
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((AudioProcessingEvent
self AudioProcessingEvent
-> Getting (JSM JSVal) AudioProcessingEvent (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String -> IndexPreservingGetter AudioProcessingEvent (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"inputBuffer") JSM JSVal -> (JSVal -> DOM AudioBuffer) -> DOM AudioBuffer
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM AudioBuffer
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)
getOutputBuffer ::
                (MonadDOM m) => AudioProcessingEvent -> m AudioBuffer
getOutputBuffer :: forall (m :: * -> *).
MonadDOM m =>
AudioProcessingEvent -> m AudioBuffer
getOutputBuffer AudioProcessingEvent
self
  = DOM AudioBuffer -> m AudioBuffer
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((AudioProcessingEvent
self AudioProcessingEvent
-> Getting (JSM JSVal) AudioProcessingEvent (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String -> IndexPreservingGetter AudioProcessingEvent (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"outputBuffer") JSM JSVal -> (JSVal -> DOM AudioBuffer) -> DOM AudioBuffer
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM AudioBuffer
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)