{-# LANGUAGE PatternSynonyms #-}
-- For HasCallStack compatibility
{-# LANGUAGE ImplicitParams, ConstraintKinds, KindSignatures #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module JSDOM.Generated.IDBObjectStore
       (put, put_, add, add_, deleteRange, deleteRange_, delete, delete_,
        getRange, getRange_, get, get_, getKeyRange, getKeyRange_, getKey,
        getKey_, clear, clear_, openCursorRange, openCursorRange_,
        openCursor, openCursor_, openKeyCursorRange, openKeyCursorRange_,
        openKeyCursor, openKeyCursor_, getAllRange, getAllRange_, getAll,
        getAll_, getAllKeysRange, getAllKeysRange_, getAllKeys,
        getAllKeys_, createIndex, createIndex_, index, index_, deleteIndex,
        countRange, countRange_, count, count_, setName, getName,
        getKeyPath, getKeyPathUnsafe, getKeyPathUnchecked, getIndexNames,
        getTransaction, getAutoIncrement, IDBObjectStore(..),
        gTypeIDBObjectStore)
       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/IDBObjectStore.put Mozilla IDBObjectStore.put documentation> 
put ::
    (MonadDOM m, ToJSVal value, ToJSVal key) =>
      IDBObjectStore -> value -> Maybe key -> m IDBRequest
put :: IDBObjectStore -> value -> Maybe key -> m IDBRequest
put IDBObjectStore
self value
value Maybe key
key
  = DOM IDBRequest -> m IDBRequest
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"put" [value -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal value
value, Maybe key -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe key
key]) JSM JSVal -> (JSVal -> DOM IDBRequest) -> DOM IDBRequest
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
         JSVal -> DOM IDBRequest
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.put Mozilla IDBObjectStore.put documentation> 
put_ ::
     (MonadDOM m, ToJSVal value, ToJSVal key) =>
       IDBObjectStore -> value -> Maybe key -> m ()
put_ :: IDBObjectStore -> value -> Maybe key -> m ()
put_ IDBObjectStore
self value
value Maybe key
key
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"put" [value -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal value
value, Maybe key -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe key
key]))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.add Mozilla IDBObjectStore.add documentation> 
add ::
    (MonadDOM m, ToJSVal value, ToJSVal key) =>
      IDBObjectStore -> value -> Maybe key -> m IDBRequest
add :: IDBObjectStore -> value -> Maybe key -> m IDBRequest
add IDBObjectStore
self value
value Maybe key
key
  = DOM IDBRequest -> m IDBRequest
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"add" [value -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal value
value, Maybe key -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe key
key]) JSM JSVal -> (JSVal -> DOM IDBRequest) -> DOM IDBRequest
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
         JSVal -> DOM IDBRequest
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.add Mozilla IDBObjectStore.add documentation> 
add_ ::
     (MonadDOM m, ToJSVal value, ToJSVal key) =>
       IDBObjectStore -> value -> Maybe key -> m ()
add_ :: IDBObjectStore -> value -> Maybe key -> m ()
add_ IDBObjectStore
self value
value Maybe key
key
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"add" [value -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal value
value, Maybe key -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe key
key]))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.delete Mozilla IDBObjectStore.delete documentation> 
deleteRange ::
            (MonadDOM m) => IDBObjectStore -> Maybe IDBKeyRange -> m IDBRequest
deleteRange :: IDBObjectStore -> Maybe IDBKeyRange -> m IDBRequest
deleteRange IDBObjectStore
self Maybe IDBKeyRange
keyRange
  = DOM IDBRequest -> m IDBRequest
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"delete" [Maybe IDBKeyRange -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBKeyRange
keyRange]) JSM JSVal -> (JSVal -> DOM IDBRequest) -> DOM IDBRequest
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM IDBRequest
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.delete Mozilla IDBObjectStore.delete documentation> 
deleteRange_ ::
             (MonadDOM m) => IDBObjectStore -> Maybe IDBKeyRange -> m ()
deleteRange_ :: IDBObjectStore -> Maybe IDBKeyRange -> m ()
deleteRange_ IDBObjectStore
self Maybe IDBKeyRange
keyRange
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"delete" [Maybe IDBKeyRange -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBKeyRange
keyRange]))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.delete Mozilla IDBObjectStore.delete documentation> 
delete ::
       (MonadDOM m, ToJSVal key) => IDBObjectStore -> key -> m IDBRequest
delete :: IDBObjectStore -> key -> m IDBRequest
delete IDBObjectStore
self key
key
  = DOM IDBRequest -> m IDBRequest
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"delete" [key -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal key
key]) JSM JSVal -> (JSVal -> DOM IDBRequest) -> DOM IDBRequest
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM IDBRequest
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.delete Mozilla IDBObjectStore.delete documentation> 
delete_ ::
        (MonadDOM m, ToJSVal key) => IDBObjectStore -> key -> m ()
delete_ :: IDBObjectStore -> key -> m ()
delete_ IDBObjectStore
self key
key
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"delete" [key -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal key
key]))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.get Mozilla IDBObjectStore.get documentation> 
getRange ::
         (MonadDOM m) => IDBObjectStore -> Maybe IDBKeyRange -> m IDBRequest
getRange :: IDBObjectStore -> Maybe IDBKeyRange -> m IDBRequest
getRange IDBObjectStore
self Maybe IDBKeyRange
key
  = DOM IDBRequest -> m IDBRequest
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"get" [Maybe IDBKeyRange -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBKeyRange
key]) JSM JSVal -> (JSVal -> DOM IDBRequest) -> DOM IDBRequest
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM IDBRequest
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.get Mozilla IDBObjectStore.get documentation> 
getRange_ ::
          (MonadDOM m) => IDBObjectStore -> Maybe IDBKeyRange -> m ()
getRange_ :: IDBObjectStore -> Maybe IDBKeyRange -> m ()
getRange_ IDBObjectStore
self Maybe IDBKeyRange
key
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"get" [Maybe IDBKeyRange -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBKeyRange
key]))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.get Mozilla IDBObjectStore.get documentation> 
get ::
    (MonadDOM m, ToJSVal key) => IDBObjectStore -> key -> m IDBRequest
get :: IDBObjectStore -> key -> m IDBRequest
get IDBObjectStore
self key
key
  = DOM IDBRequest -> m IDBRequest
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"get" [key -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal key
key]) JSM JSVal -> (JSVal -> DOM IDBRequest) -> DOM IDBRequest
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM IDBRequest
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.get Mozilla IDBObjectStore.get documentation> 
get_ :: (MonadDOM m, ToJSVal key) => IDBObjectStore -> key -> m ()
get_ :: IDBObjectStore -> key -> m ()
get_ IDBObjectStore
self key
key = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"get" [key -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal key
key]))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.getKey Mozilla IDBObjectStore.getKey documentation> 
getKeyRange ::
            (MonadDOM m) => IDBObjectStore -> Maybe IDBKeyRange -> m IDBRequest
getKeyRange :: IDBObjectStore -> Maybe IDBKeyRange -> m IDBRequest
getKeyRange IDBObjectStore
self Maybe IDBKeyRange
key
  = DOM IDBRequest -> m IDBRequest
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"getKey" [Maybe IDBKeyRange -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBKeyRange
key]) JSM JSVal -> (JSVal -> DOM IDBRequest) -> DOM IDBRequest
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM IDBRequest
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.getKey Mozilla IDBObjectStore.getKey documentation> 
getKeyRange_ ::
             (MonadDOM m) => IDBObjectStore -> Maybe IDBKeyRange -> m ()
getKeyRange_ :: IDBObjectStore -> Maybe IDBKeyRange -> m ()
getKeyRange_ IDBObjectStore
self Maybe IDBKeyRange
key
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"getKey" [Maybe IDBKeyRange -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBKeyRange
key]))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.getKey Mozilla IDBObjectStore.getKey documentation> 
getKey ::
       (MonadDOM m, ToJSVal key) => IDBObjectStore -> key -> m IDBRequest
getKey :: IDBObjectStore -> key -> m IDBRequest
getKey IDBObjectStore
self key
key
  = DOM IDBRequest -> m IDBRequest
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"getKey" [key -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal key
key]) JSM JSVal -> (JSVal -> DOM IDBRequest) -> DOM IDBRequest
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM IDBRequest
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.getKey Mozilla IDBObjectStore.getKey documentation> 
getKey_ ::
        (MonadDOM m, ToJSVal key) => IDBObjectStore -> key -> m ()
getKey_ :: IDBObjectStore -> key -> m ()
getKey_ IDBObjectStore
self key
key
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"getKey" [key -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal key
key]))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.clear Mozilla IDBObjectStore.clear documentation> 
clear :: (MonadDOM m) => IDBObjectStore -> m IDBRequest
clear :: IDBObjectStore -> m IDBRequest
clear IDBObjectStore
self
  = DOM IDBRequest -> m IDBRequest
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> () -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"clear" ()) JSM JSVal -> (JSVal -> DOM IDBRequest) -> DOM IDBRequest
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM IDBRequest
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.clear Mozilla IDBObjectStore.clear documentation> 
clear_ :: (MonadDOM m) => IDBObjectStore -> m ()
clear_ :: IDBObjectStore -> m ()
clear_ IDBObjectStore
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 (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> () -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"clear" ()))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.openCursor Mozilla IDBObjectStore.openCursor documentation> 
openCursorRange ::
                (MonadDOM m) =>
                  IDBObjectStore ->
                    Maybe IDBKeyRange -> Maybe IDBCursorDirection -> m IDBRequest
openCursorRange :: IDBObjectStore
-> Maybe IDBKeyRange -> Maybe IDBCursorDirection -> m IDBRequest
openCursorRange IDBObjectStore
self Maybe IDBKeyRange
range Maybe IDBCursorDirection
direction
  = DOM IDBRequest -> m IDBRequest
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"openCursor" [Maybe IDBKeyRange -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBKeyRange
range, Maybe IDBCursorDirection -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBCursorDirection
direction]) JSM JSVal -> (JSVal -> DOM IDBRequest) -> DOM IDBRequest
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
         JSVal -> DOM IDBRequest
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.openCursor Mozilla IDBObjectStore.openCursor documentation> 
openCursorRange_ ::
                 (MonadDOM m) =>
                   IDBObjectStore ->
                     Maybe IDBKeyRange -> Maybe IDBCursorDirection -> m ()
openCursorRange_ :: IDBObjectStore
-> Maybe IDBKeyRange -> Maybe IDBCursorDirection -> m ()
openCursorRange_ IDBObjectStore
self Maybe IDBKeyRange
range Maybe IDBCursorDirection
direction
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void
         (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"openCursor" [Maybe IDBKeyRange -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBKeyRange
range, Maybe IDBCursorDirection -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBCursorDirection
direction]))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.openCursor Mozilla IDBObjectStore.openCursor documentation> 
openCursor ::
           (MonadDOM m, ToJSVal key) =>
             IDBObjectStore -> key -> Maybe IDBCursorDirection -> m IDBRequest
openCursor :: IDBObjectStore -> key -> Maybe IDBCursorDirection -> m IDBRequest
openCursor IDBObjectStore
self key
key Maybe IDBCursorDirection
direction
  = DOM IDBRequest -> m IDBRequest
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"openCursor" [key -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal key
key, Maybe IDBCursorDirection -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBCursorDirection
direction]) JSM JSVal -> (JSVal -> DOM IDBRequest) -> DOM IDBRequest
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
         JSVal -> DOM IDBRequest
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.openCursor Mozilla IDBObjectStore.openCursor documentation> 
openCursor_ ::
            (MonadDOM m, ToJSVal key) =>
              IDBObjectStore -> key -> Maybe IDBCursorDirection -> m ()
openCursor_ :: IDBObjectStore -> key -> Maybe IDBCursorDirection -> m ()
openCursor_ IDBObjectStore
self key
key Maybe IDBCursorDirection
direction
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"openCursor" [key -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal key
key, Maybe IDBCursorDirection -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBCursorDirection
direction]))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.openKeyCursor Mozilla IDBObjectStore.openKeyCursor documentation> 
openKeyCursorRange ::
                   (MonadDOM m) =>
                     IDBObjectStore ->
                       Maybe IDBKeyRange -> Maybe IDBCursorDirection -> m IDBRequest
openKeyCursorRange :: IDBObjectStore
-> Maybe IDBKeyRange -> Maybe IDBCursorDirection -> m IDBRequest
openKeyCursorRange IDBObjectStore
self Maybe IDBKeyRange
range Maybe IDBCursorDirection
direction
  = DOM IDBRequest -> m IDBRequest
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"openKeyCursor" [Maybe IDBKeyRange -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBKeyRange
range, Maybe IDBCursorDirection -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBCursorDirection
direction])
         JSM JSVal -> (JSVal -> DOM IDBRequest) -> DOM IDBRequest
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM IDBRequest
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.openKeyCursor Mozilla IDBObjectStore.openKeyCursor documentation> 
openKeyCursorRange_ ::
                    (MonadDOM m) =>
                      IDBObjectStore ->
                        Maybe IDBKeyRange -> Maybe IDBCursorDirection -> m ()
openKeyCursorRange_ :: IDBObjectStore
-> Maybe IDBKeyRange -> Maybe IDBCursorDirection -> m ()
openKeyCursorRange_ IDBObjectStore
self Maybe IDBKeyRange
range Maybe IDBCursorDirection
direction
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void
         (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"openKeyCursor" [Maybe IDBKeyRange -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBKeyRange
range, Maybe IDBCursorDirection -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBCursorDirection
direction]))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.openKeyCursor Mozilla IDBObjectStore.openKeyCursor documentation> 
openKeyCursor ::
              (MonadDOM m, ToJSVal key) =>
                IDBObjectStore -> key -> Maybe IDBCursorDirection -> m IDBRequest
openKeyCursor :: IDBObjectStore -> key -> Maybe IDBCursorDirection -> m IDBRequest
openKeyCursor IDBObjectStore
self key
key Maybe IDBCursorDirection
direction
  = DOM IDBRequest -> m IDBRequest
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"openKeyCursor" [key -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal key
key, Maybe IDBCursorDirection -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBCursorDirection
direction]) JSM JSVal -> (JSVal -> DOM IDBRequest) -> DOM IDBRequest
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
         JSVal -> DOM IDBRequest
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.openKeyCursor Mozilla IDBObjectStore.openKeyCursor documentation> 
openKeyCursor_ ::
               (MonadDOM m, ToJSVal key) =>
                 IDBObjectStore -> key -> Maybe IDBCursorDirection -> m ()
openKeyCursor_ :: IDBObjectStore -> key -> Maybe IDBCursorDirection -> m ()
openKeyCursor_ IDBObjectStore
self key
key Maybe IDBCursorDirection
direction
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void
         (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"openKeyCursor" [key -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal key
key, Maybe IDBCursorDirection -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBCursorDirection
direction]))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.getAll Mozilla IDBObjectStore.getAll documentation> 
getAllRange ::
            (MonadDOM m) =>
              IDBObjectStore -> Maybe IDBKeyRange -> Maybe Word -> m IDBRequest
getAllRange :: IDBObjectStore -> Maybe IDBKeyRange -> Maybe Word -> m IDBRequest
getAllRange IDBObjectStore
self Maybe IDBKeyRange
range Maybe Word
count
  = DOM IDBRequest -> m IDBRequest
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"getAll" [Maybe IDBKeyRange -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBKeyRange
range, Maybe Word -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe Word
count]) JSM JSVal -> (JSVal -> DOM IDBRequest) -> DOM IDBRequest
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
         JSVal -> DOM IDBRequest
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.getAll Mozilla IDBObjectStore.getAll documentation> 
getAllRange_ ::
             (MonadDOM m) =>
               IDBObjectStore -> Maybe IDBKeyRange -> Maybe Word -> m ()
getAllRange_ :: IDBObjectStore -> Maybe IDBKeyRange -> Maybe Word -> m ()
getAllRange_ IDBObjectStore
self Maybe IDBKeyRange
range Maybe Word
count
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"getAll" [Maybe IDBKeyRange -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBKeyRange
range, Maybe Word -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe Word
count]))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.getAll Mozilla IDBObjectStore.getAll documentation> 
getAll ::
       (MonadDOM m, ToJSVal key) =>
         IDBObjectStore -> key -> Maybe Word -> m IDBRequest
getAll :: IDBObjectStore -> key -> Maybe Word -> m IDBRequest
getAll IDBObjectStore
self key
key Maybe Word
count
  = DOM IDBRequest -> m IDBRequest
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"getAll" [key -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal key
key, Maybe Word -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe Word
count]) JSM JSVal -> (JSVal -> DOM IDBRequest) -> DOM IDBRequest
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
         JSVal -> DOM IDBRequest
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.getAll Mozilla IDBObjectStore.getAll documentation> 
getAll_ ::
        (MonadDOM m, ToJSVal key) =>
          IDBObjectStore -> key -> Maybe Word -> m ()
getAll_ :: IDBObjectStore -> key -> Maybe Word -> m ()
getAll_ IDBObjectStore
self key
key Maybe Word
count
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"getAll" [key -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal key
key, Maybe Word -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe Word
count]))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.getAllKeys Mozilla IDBObjectStore.getAllKeys documentation> 
getAllKeysRange ::
                (MonadDOM m) =>
                  IDBObjectStore -> Maybe IDBKeyRange -> Maybe Word -> m IDBRequest
getAllKeysRange :: IDBObjectStore -> Maybe IDBKeyRange -> Maybe Word -> m IDBRequest
getAllKeysRange IDBObjectStore
self Maybe IDBKeyRange
range Maybe Word
count
  = DOM IDBRequest -> m IDBRequest
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"getAllKeys" [Maybe IDBKeyRange -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBKeyRange
range, Maybe Word -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe Word
count]) JSM JSVal -> (JSVal -> DOM IDBRequest) -> DOM IDBRequest
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
         JSVal -> DOM IDBRequest
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.getAllKeys Mozilla IDBObjectStore.getAllKeys documentation> 
getAllKeysRange_ ::
                 (MonadDOM m) =>
                   IDBObjectStore -> Maybe IDBKeyRange -> Maybe Word -> m ()
getAllKeysRange_ :: IDBObjectStore -> Maybe IDBKeyRange -> Maybe Word -> m ()
getAllKeysRange_ IDBObjectStore
self Maybe IDBKeyRange
range Maybe Word
count
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"getAllKeys" [Maybe IDBKeyRange -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBKeyRange
range, Maybe Word -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe Word
count]))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.getAllKeys Mozilla IDBObjectStore.getAllKeys documentation> 
getAllKeys ::
           (MonadDOM m, ToJSVal key) =>
             IDBObjectStore -> key -> Maybe Word -> m IDBRequest
getAllKeys :: IDBObjectStore -> key -> Maybe Word -> m IDBRequest
getAllKeys IDBObjectStore
self key
key Maybe Word
count
  = DOM IDBRequest -> m IDBRequest
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"getAllKeys" [key -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal key
key, Maybe Word -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe Word
count]) JSM JSVal -> (JSVal -> DOM IDBRequest) -> DOM IDBRequest
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
         JSVal -> DOM IDBRequest
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.getAllKeys Mozilla IDBObjectStore.getAllKeys documentation> 
getAllKeys_ ::
            (MonadDOM m, ToJSVal key) =>
              IDBObjectStore -> key -> Maybe Word -> m ()
getAllKeys_ :: IDBObjectStore -> key -> Maybe Word -> m ()
getAllKeys_ IDBObjectStore
self key
key Maybe Word
count
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"getAllKeys" [key -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal key
key, Maybe Word -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe Word
count]))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.createIndex Mozilla IDBObjectStore.createIndex documentation> 
createIndex ::
            (MonadDOM m, ToJSString name, IsStringOrStrings keyPath) =>
              IDBObjectStore ->
                name -> keyPath -> Maybe IDBIndexParameters -> m IDBIndex
createIndex :: IDBObjectStore
-> name -> keyPath -> Maybe IDBIndexParameters -> m IDBIndex
createIndex IDBObjectStore
self name
name keyPath
keyPath Maybe IDBIndexParameters
options
  = DOM IDBIndex -> m IDBIndex
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"createIndex"
          [name -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal name
name, keyPath -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal keyPath
keyPath, Maybe IDBIndexParameters -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBIndexParameters
options])
         JSM JSVal -> (JSVal -> DOM IDBIndex) -> DOM IDBIndex
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM IDBIndex
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.createIndex Mozilla IDBObjectStore.createIndex documentation> 
createIndex_ ::
             (MonadDOM m, ToJSString name, IsStringOrStrings keyPath) =>
               IDBObjectStore ->
                 name -> keyPath -> Maybe IDBIndexParameters -> m ()
createIndex_ :: IDBObjectStore
-> name -> keyPath -> Maybe IDBIndexParameters -> m ()
createIndex_ IDBObjectStore
self name
name keyPath
keyPath Maybe IDBIndexParameters
options
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void
         (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"createIndex"
            [name -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal name
name, keyPath -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal keyPath
keyPath, Maybe IDBIndexParameters -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBIndexParameters
options]))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.index Mozilla IDBObjectStore.index documentation> 
index ::
      (MonadDOM m, ToJSString name) =>
        IDBObjectStore -> name -> m IDBIndex
index :: IDBObjectStore -> name -> m IDBIndex
index IDBObjectStore
self name
name
  = DOM IDBIndex -> m IDBIndex
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"index" [name -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal name
name]) JSM JSVal -> (JSVal -> DOM IDBIndex) -> DOM IDBIndex
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM IDBIndex
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.index Mozilla IDBObjectStore.index documentation> 
index_ ::
       (MonadDOM m, ToJSString name) => IDBObjectStore -> name -> m ()
index_ :: IDBObjectStore -> name -> m ()
index_ IDBObjectStore
self name
name
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"index" [name -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal name
name]))

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

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.count Mozilla IDBObjectStore.count documentation> 
countRange ::
           (MonadDOM m) => IDBObjectStore -> Maybe IDBKeyRange -> m IDBRequest
countRange :: IDBObjectStore -> Maybe IDBKeyRange -> m IDBRequest
countRange IDBObjectStore
self Maybe IDBKeyRange
range
  = DOM IDBRequest -> m IDBRequest
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"count" [Maybe IDBKeyRange -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBKeyRange
range]) JSM JSVal -> (JSVal -> DOM IDBRequest) -> DOM IDBRequest
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM IDBRequest
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.count Mozilla IDBObjectStore.count documentation> 
countRange_ ::
            (MonadDOM m) => IDBObjectStore -> Maybe IDBKeyRange -> m ()
countRange_ :: IDBObjectStore -> Maybe IDBKeyRange -> m ()
countRange_ IDBObjectStore
self Maybe IDBKeyRange
range
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"count" [Maybe IDBKeyRange -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal Maybe IDBKeyRange
range]))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.count Mozilla IDBObjectStore.count documentation> 
count ::
      (MonadDOM m, ToJSVal key) => IDBObjectStore -> key -> m IDBRequest
count :: IDBObjectStore -> key -> m IDBRequest
count IDBObjectStore
self key
key
  = DOM IDBRequest -> m IDBRequest
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"count" [key -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal key
key]) JSM JSVal -> (JSVal -> DOM IDBRequest) -> DOM IDBRequest
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM IDBRequest
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.count Mozilla IDBObjectStore.count documentation> 
count_ ::
       (MonadDOM m, ToJSVal key) => IDBObjectStore -> key -> m ()
count_ :: IDBObjectStore -> key -> m ()
count_ IDBObjectStore
self key
key
  = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (JSM JSVal -> DOM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> [JSM JSVal] -> JSF
forall name args.
(ToJSString name, MakeArgs args) =>
name -> args -> JSF
jsf [Char]
"count" [key -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal key
key]))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.name Mozilla IDBObjectStore.name documentation> 
setName ::
        (MonadDOM m, ToJSString val) => IDBObjectStore -> val -> m ()
setName :: IDBObjectStore -> val -> m ()
setName IDBObjectStore
self val
val = DOM () -> m ()
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM (IDBObjectStore
self IDBObjectStore
-> Getting (DOM ()) IDBObjectStore (DOM ()) -> DOM ()
forall s a. s -> Getting a s a -> a
^. [Char]
-> JSM JSVal
-> forall o. MakeObject o => IndexPreservingGetter o (DOM ())
forall name val.
(ToJSString name, ToJSVal val) =>
name
-> val
-> forall o. MakeObject o => IndexPreservingGetter o (DOM ())
jss [Char]
"name" (val -> JSM JSVal
forall a. ToJSVal a => a -> JSM JSVal
toJSVal val
val))

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.name Mozilla IDBObjectStore.name documentation> 
getName ::
        (MonadDOM m, FromJSString result) => IDBObjectStore -> m result
getName :: IDBObjectStore -> m result
getName IDBObjectStore
self = DOM result -> m result
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> IndexPreservingGetter IDBObjectStore (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js [Char]
"name") JSM JSVal -> (JSVal -> DOM result) -> DOM result
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM result
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.keyPath Mozilla IDBObjectStore.keyPath documentation> 
getKeyPath ::
           (MonadDOM m) => IDBObjectStore -> m (Maybe IDBKeyPath)
getKeyPath :: IDBObjectStore -> m (Maybe IDBKeyPath)
getKeyPath IDBObjectStore
self = DOM (Maybe IDBKeyPath) -> m (Maybe IDBKeyPath)
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> IndexPreservingGetter IDBObjectStore (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js [Char]
"keyPath") JSM JSVal
-> (JSVal -> DOM (Maybe IDBKeyPath)) -> DOM (Maybe IDBKeyPath)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM (Maybe IDBKeyPath)
forall a. FromJSVal a => JSVal -> JSM (Maybe a)
fromJSVal)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.keyPath Mozilla IDBObjectStore.keyPath documentation> 
getKeyPathUnsafe ::
                 (MonadDOM m, HasCallStack) => IDBObjectStore -> m IDBKeyPath
getKeyPathUnsafe :: IDBObjectStore -> m IDBKeyPath
getKeyPathUnsafe IDBObjectStore
self
  = DOM IDBKeyPath -> m IDBKeyPath
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM
      (((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> IndexPreservingGetter IDBObjectStore (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js [Char]
"keyPath") JSM JSVal
-> (JSVal -> DOM (Maybe IDBKeyPath)) -> DOM (Maybe IDBKeyPath)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM (Maybe IDBKeyPath)
forall a. FromJSVal a => JSVal -> JSM (Maybe a)
fromJSVal) DOM (Maybe IDBKeyPath)
-> (Maybe IDBKeyPath -> DOM IDBKeyPath) -> DOM IDBKeyPath
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
         DOM IDBKeyPath
-> (IDBKeyPath -> DOM IDBKeyPath)
-> Maybe IDBKeyPath
-> DOM IDBKeyPath
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Char] -> DOM IDBKeyPath
forall a. HasCallStack => [Char] -> a
Prelude.error [Char]
"Nothing to return") IDBKeyPath -> DOM IDBKeyPath
forall (m :: * -> *) a. Monad m => a -> m a
return)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.keyPath Mozilla IDBObjectStore.keyPath documentation> 
getKeyPathUnchecked ::
                    (MonadDOM m) => IDBObjectStore -> m IDBKeyPath
getKeyPathUnchecked :: IDBObjectStore -> m IDBKeyPath
getKeyPathUnchecked IDBObjectStore
self
  = DOM IDBKeyPath -> m IDBKeyPath
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> IndexPreservingGetter IDBObjectStore (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js [Char]
"keyPath") JSM JSVal -> (JSVal -> DOM IDBKeyPath) -> DOM IDBKeyPath
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM IDBKeyPath
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.indexNames Mozilla IDBObjectStore.indexNames documentation> 
getIndexNames :: (MonadDOM m) => IDBObjectStore -> m DOMStringList
getIndexNames :: IDBObjectStore -> m DOMStringList
getIndexNames IDBObjectStore
self
  = DOM DOMStringList -> m DOMStringList
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> IndexPreservingGetter IDBObjectStore (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js [Char]
"indexNames") JSM JSVal -> (JSVal -> DOM DOMStringList) -> DOM DOMStringList
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM DOMStringList
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.transaction Mozilla IDBObjectStore.transaction documentation> 
getTransaction ::
               (MonadDOM m) => IDBObjectStore -> m IDBTransaction
getTransaction :: IDBObjectStore -> m IDBTransaction
getTransaction IDBObjectStore
self
  = DOM IDBTransaction -> m IDBTransaction
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> IndexPreservingGetter IDBObjectStore (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js [Char]
"transaction") JSM JSVal -> (JSVal -> DOM IDBTransaction) -> DOM IDBTransaction
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM IDBTransaction
forall a. FromJSVal a => JSVal -> JSM a
fromJSValUnchecked)

-- | <https://developer.mozilla.org/en-US/docs/Web/API/IDBObjectStore.autoIncrement Mozilla IDBObjectStore.autoIncrement documentation> 
getAutoIncrement :: (MonadDOM m) => IDBObjectStore -> m Bool
getAutoIncrement :: IDBObjectStore -> m Bool
getAutoIncrement IDBObjectStore
self
  = DOM Bool -> m Bool
forall (m :: * -> *) a. MonadDOM m => DOM a -> m a
liftDOM ((IDBObjectStore
self IDBObjectStore
-> Getting (JSM JSVal) IDBObjectStore (JSM JSVal) -> JSM JSVal
forall s a. s -> Getting a s a -> a
^. [Char] -> IndexPreservingGetter IDBObjectStore (JSM JSVal)
forall s name.
(MakeObject s, ToJSString name) =>
name -> IndexPreservingGetter s (JSM JSVal)
js [Char]
"autoIncrement") JSM JSVal -> (JSVal -> DOM Bool) -> DOM Bool
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= JSVal -> DOM Bool
forall value. ToJSVal value => value -> DOM Bool
valToBool)