{-# LANGUAGE PatternSynonyms #-}
-- For HasCallStack compatibility
{-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module JSDOM.Generated.MediaKeySystemAccess
       (getConfiguration, getConfiguration_, createMediaKeys,
        createMediaKeys_, getKeySystem, MediaKeySystemAccess(..),
        gTypeMediaKeySystemAccess)
       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

-- | <https://developer.mozilla.org/en-US/docs/Web/API/MediaKeySystemAccess.getConfiguration Mozilla MediaKeySystemAccess.getConfiguration documentation> 
getConfiguration ::
                 (MonadDOM m) =>
                   MediaKeySystemAccess -> m MediaKeySystemConfiguration
getConfiguration :: forall (m :: * -> *).
MonadDOM m =>
MediaKeySystemAccess -> m MediaKeySystemConfiguration
getConfiguration MediaKeySystemAccess
self
  = DOM MediaKeySystemConfiguration -> m MediaKeySystemConfiguration
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((MediaKeySystemAccess
self MediaKeySystemAccess
-> Getting (JSM JSVal) MediaKeySystemAccess (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String -> () -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf String
"getConfiguration" ()) JSM JSVal
-> (JSVal -> DOM MediaKeySystemConfiguration)
-> DOM MediaKeySystemConfiguration
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 MediaKeySystemConfiguration
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/MediaKeySystemAccess.getConfiguration Mozilla MediaKeySystemAccess.getConfiguration documentation> 
getConfiguration_ :: (MonadDOM m) => MediaKeySystemAccess -> m ()
getConfiguration_ :: forall (m :: * -> *). MonadDOM m => MediaKeySystemAccess -> m ()
getConfiguration_ MediaKeySystemAccess
self
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (MediaKeySystemAccess
self MediaKeySystemAccess
-> Getting (JSM JSVal) MediaKeySystemAccess (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String -> () -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf String
"getConfiguration" ()))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/MediaKeySystemAccess.createMediaKeys Mozilla MediaKeySystemAccess.createMediaKeys documentation> 
createMediaKeys ::
                (MonadDOM m) => MediaKeySystemAccess -> m MediaKeys
createMediaKeys :: forall (m :: * -> *).
MonadDOM m =>
MediaKeySystemAccess -> m MediaKeys
createMediaKeys MediaKeySystemAccess
self
  = DOM MediaKeys -> m MediaKeys
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      (((MediaKeySystemAccess
self MediaKeySystemAccess
-> Getting (JSM JSVal) MediaKeySystemAccess (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String -> () -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf String
"createMediaKeys" ()) JSM JSVal -> (JSVal -> JSM JSVal) -> JSM JSVal
forall a b. JSM a -> (a -> JSM b) -> JSM b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> JSM JSVal
readPromise) JSM JSVal -> (JSVal -> DOM MediaKeys) -> DOM MediaKeys
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 MediaKeys
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/MediaKeySystemAccess.createMediaKeys Mozilla MediaKeySystemAccess.createMediaKeys documentation> 
createMediaKeys_ :: (MonadDOM m) => MediaKeySystemAccess -> m ()
createMediaKeys_ :: forall (m :: * -> *). MonadDOM m => MediaKeySystemAccess -> m ()
createMediaKeys_ MediaKeySystemAccess
self
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (MediaKeySystemAccess
self MediaKeySystemAccess
-> Getting (JSM JSVal) MediaKeySystemAccess (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String -> () -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf String
"createMediaKeys" ()))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/MediaKeySystemAccess.keySystem Mozilla MediaKeySystemAccess.keySystem documentation> 
getKeySystem ::
             (MonadDOM m, FromJSString result) =>
               MediaKeySystemAccess -> m result
getKeySystem :: forall (m :: * -> *) result.
(MonadDOM m, FromJSString result) =>
MediaKeySystemAccess -> m result
getKeySystem MediaKeySystemAccess
self
  = DOM result -> m result
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((MediaKeySystemAccess
self MediaKeySystemAccess
-> Getting (JSM JSVal) MediaKeySystemAccess (JSM JSVal)
-> JSM JSVal
forall s a. s -> Getting a s a -> a
^. String -> IndexPreservingGetter MediaKeySystemAccess (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js String
"keySystem") JSM JSVal -> (JSVal -> DOM result) -> DOM result
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 result
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)