{-# LANGUAGE PatternSynonyms #-}
-- For HasCallStack compatibility
{-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module JSDOM.Generated.StorageQuotaCallback
       (newStorageQuotaCallback, newStorageQuotaCallbackSync,
        newStorageQuotaCallbackAsync, StorageQuotaCallback)
       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/StorageQuotaCallback Mozilla StorageQuotaCallback documentation> 
newStorageQuotaCallback ::
                        (MonadDOM m) => (Double -> JSM ()) -> m StorageQuotaCallback
newStorageQuotaCallback :: (Double -> JSM ()) -> m StorageQuotaCallback
newStorageQuotaCallback Double -> JSM ()
callback
  = DOM StorageQuotaCallback -> m StorageQuotaCallback
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      (Callback (JSVal -> IO ()) -> StorageQuotaCallback
StorageQuotaCallback (Callback (JSVal -> IO ()) -> StorageQuotaCallback)
-> (Function -> Callback (JSVal -> IO ()))
-> Function
-> StorageQuotaCallback
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Function -> Callback (JSVal -> IO ())
forall a. Function -> Callback a
Callback (Function -> StorageQuotaCallback)
-> JSM Function -> DOM StorageQuotaCallback
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
         JSCallAsFunction -> JSM Function
function
           (\ JSVal
_ JSVal
_ [JSVal
grantedQuotaInBytes] ->
              JSVal -> JSM Double
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked JSVal
grantedQuotaInBytes JSM Double -> (Double -> JSM ()) -> JSM ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                \ Double
grantedQuotaInBytes' -> Double -> JSM ()
callback Double
grantedQuotaInBytes'))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/StorageQuotaCallback Mozilla StorageQuotaCallback documentation> 
newStorageQuotaCallbackSync ::
                            (MonadDOM m) => (Double -> JSM ()) -> m StorageQuotaCallback
newStorageQuotaCallbackSync :: (Double -> JSM ()) -> m StorageQuotaCallback
newStorageQuotaCallbackSync Double -> JSM ()
callback
  = DOM StorageQuotaCallback -> m StorageQuotaCallback
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      (Callback (JSVal -> IO ()) -> StorageQuotaCallback
StorageQuotaCallback (Callback (JSVal -> IO ()) -> StorageQuotaCallback)
-> (Function -> Callback (JSVal -> IO ()))
-> Function
-> StorageQuotaCallback
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Function -> Callback (JSVal -> IO ())
forall a. Function -> Callback a
Callback (Function -> StorageQuotaCallback)
-> JSM Function -> DOM StorageQuotaCallback
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
         JSCallAsFunction -> JSM Function
function
           (\ JSVal
_ JSVal
_ [JSVal
grantedQuotaInBytes] ->
              JSVal -> JSM Double
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked JSVal
grantedQuotaInBytes JSM Double -> (Double -> JSM ()) -> JSM ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                \ Double
grantedQuotaInBytes' -> Double -> JSM ()
callback Double
grantedQuotaInBytes'))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/StorageQuotaCallback Mozilla StorageQuotaCallback documentation> 
newStorageQuotaCallbackAsync ::
                             (MonadDOM m) => (Double -> JSM ()) -> m StorageQuotaCallback
newStorageQuotaCallbackAsync :: (Double -> JSM ()) -> m StorageQuotaCallback
newStorageQuotaCallbackAsync Double -> JSM ()
callback
  = DOM StorageQuotaCallback -> m StorageQuotaCallback
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      (Callback (JSVal -> IO ()) -> StorageQuotaCallback
StorageQuotaCallback (Callback (JSVal -> IO ()) -> StorageQuotaCallback)
-> (Function -> Callback (JSVal -> IO ()))
-> Function
-> StorageQuotaCallback
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Function -> Callback (JSVal -> IO ())
forall a. Function -> Callback a
Callback (Function -> StorageQuotaCallback)
-> JSM Function -> DOM StorageQuotaCallback
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
         JSCallAsFunction -> JSM Function
asyncFunction
           (\ JSVal
_ JSVal
_ [JSVal
grantedQuotaInBytes] ->
              JSVal -> JSM Double
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked JSVal
grantedQuotaInBytes JSM Double -> (Double -> JSM ()) -> JSM ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                \ Double
grantedQuotaInBytes' -> Double -> JSM ()
callback Double
grantedQuotaInBytes'))