{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)
-}

module GI.WebKit.Objects.DOMMemoryInfo
    ( 

-- * Exported types
    DOMMemoryInfo(..)                       ,
    DOMMemoryInfoK                          ,
    toDOMMemoryInfo                         ,
    noDOMMemoryInfo                         ,


 -- * Methods
-- ** dOMMemoryInfoGetJsHeapSizeLimit
    dOMMemoryInfoGetJsHeapSizeLimit         ,


-- ** dOMMemoryInfoGetTotalJsHeapSize
    dOMMemoryInfoGetTotalJsHeapSize         ,


-- ** dOMMemoryInfoGetUsedJsHeapSize
    dOMMemoryInfoGetUsedJsHeapSize          ,




 -- * Properties
-- ** JsHeapSizeLimit
    DOMMemoryInfoJsHeapSizeLimitPropertyInfo,
    getDOMMemoryInfoJsHeapSizeLimit         ,


-- ** TotalJsHeapSize
    DOMMemoryInfoTotalJsHeapSizePropertyInfo,
    getDOMMemoryInfoTotalJsHeapSize         ,


-- ** UsedJsHeapSize
    DOMMemoryInfoUsedJsHeapSizePropertyInfo ,
    getDOMMemoryInfoUsedJsHeapSize          ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.WebKit.Types
import GI.WebKit.Callbacks
import qualified GI.GObject as GObject

newtype DOMMemoryInfo = DOMMemoryInfo (ForeignPtr DOMMemoryInfo)
foreign import ccall "webkit_dom_memory_info_get_type"
    c_webkit_dom_memory_info_get_type :: IO GType

type instance ParentTypes DOMMemoryInfo = DOMMemoryInfoParentTypes
type DOMMemoryInfoParentTypes = '[DOMObject, GObject.Object]

instance GObject DOMMemoryInfo where
    gobjectIsInitiallyUnowned _ = False
    gobjectType _ = c_webkit_dom_memory_info_get_type
    

class GObject o => DOMMemoryInfoK o
instance (GObject o, IsDescendantOf DOMMemoryInfo o) => DOMMemoryInfoK o

toDOMMemoryInfo :: DOMMemoryInfoK o => o -> IO DOMMemoryInfo
toDOMMemoryInfo = unsafeCastTo DOMMemoryInfo

noDOMMemoryInfo :: Maybe DOMMemoryInfo
noDOMMemoryInfo = Nothing

-- VVV Prop "js-heap-size-limit"
   -- Type: TBasicType TUInt64
   -- Flags: [PropertyReadable]

getDOMMemoryInfoJsHeapSizeLimit :: (MonadIO m, DOMMemoryInfoK o) => o -> m Word64
getDOMMemoryInfoJsHeapSizeLimit obj = liftIO $ getObjectPropertyUInt64 obj "js-heap-size-limit"

data DOMMemoryInfoJsHeapSizeLimitPropertyInfo
instance AttrInfo DOMMemoryInfoJsHeapSizeLimitPropertyInfo where
    type AttrAllowedOps DOMMemoryInfoJsHeapSizeLimitPropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMMemoryInfoJsHeapSizeLimitPropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMMemoryInfoJsHeapSizeLimitPropertyInfo = DOMMemoryInfoK
    type AttrGetType DOMMemoryInfoJsHeapSizeLimitPropertyInfo = Word64
    type AttrLabel DOMMemoryInfoJsHeapSizeLimitPropertyInfo = "DOMMemoryInfo::js-heap-size-limit"
    attrGet _ = getDOMMemoryInfoJsHeapSizeLimit
    attrSet _ = undefined
    attrConstruct _ = undefined

-- VVV Prop "total-js-heap-size"
   -- Type: TBasicType TUInt64
   -- Flags: [PropertyReadable]

getDOMMemoryInfoTotalJsHeapSize :: (MonadIO m, DOMMemoryInfoK o) => o -> m Word64
getDOMMemoryInfoTotalJsHeapSize obj = liftIO $ getObjectPropertyUInt64 obj "total-js-heap-size"

data DOMMemoryInfoTotalJsHeapSizePropertyInfo
instance AttrInfo DOMMemoryInfoTotalJsHeapSizePropertyInfo where
    type AttrAllowedOps DOMMemoryInfoTotalJsHeapSizePropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMMemoryInfoTotalJsHeapSizePropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMMemoryInfoTotalJsHeapSizePropertyInfo = DOMMemoryInfoK
    type AttrGetType DOMMemoryInfoTotalJsHeapSizePropertyInfo = Word64
    type AttrLabel DOMMemoryInfoTotalJsHeapSizePropertyInfo = "DOMMemoryInfo::total-js-heap-size"
    attrGet _ = getDOMMemoryInfoTotalJsHeapSize
    attrSet _ = undefined
    attrConstruct _ = undefined

-- VVV Prop "used-js-heap-size"
   -- Type: TBasicType TUInt64
   -- Flags: [PropertyReadable]

getDOMMemoryInfoUsedJsHeapSize :: (MonadIO m, DOMMemoryInfoK o) => o -> m Word64
getDOMMemoryInfoUsedJsHeapSize obj = liftIO $ getObjectPropertyUInt64 obj "used-js-heap-size"

data DOMMemoryInfoUsedJsHeapSizePropertyInfo
instance AttrInfo DOMMemoryInfoUsedJsHeapSizePropertyInfo where
    type AttrAllowedOps DOMMemoryInfoUsedJsHeapSizePropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMMemoryInfoUsedJsHeapSizePropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMMemoryInfoUsedJsHeapSizePropertyInfo = DOMMemoryInfoK
    type AttrGetType DOMMemoryInfoUsedJsHeapSizePropertyInfo = Word64
    type AttrLabel DOMMemoryInfoUsedJsHeapSizePropertyInfo = "DOMMemoryInfo::used-js-heap-size"
    attrGet _ = getDOMMemoryInfoUsedJsHeapSize
    attrSet _ = undefined
    attrConstruct _ = undefined

type instance AttributeList DOMMemoryInfo = DOMMemoryInfoAttributeList
type DOMMemoryInfoAttributeList = ('[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("js-heap-size-limit", DOMMemoryInfoJsHeapSizeLimitPropertyInfo), '("total-js-heap-size", DOMMemoryInfoTotalJsHeapSizePropertyInfo), '("used-js-heap-size", DOMMemoryInfoUsedJsHeapSizePropertyInfo)] :: [(Symbol, *)])

type instance SignalList DOMMemoryInfo = DOMMemoryInfoSignalList
type DOMMemoryInfoSignalList = ('[ '("notify", GObject.ObjectNotifySignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

-- method DOMMemoryInfo::get_js_heap_size_limit
-- method type : MemberFunction
-- Args : [Arg {argName = "self", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "self", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt64
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_memory_info_get_js_heap_size_limit" webkit_dom_memory_info_get_js_heap_size_limit :: 
    Ptr () ->                               -- self : TBasicType TVoid
    IO Word64

{-# DEPRECATED dOMMemoryInfoGetJsHeapSizeLimit ["(Since version 2.2)"]#-}
dOMMemoryInfoGetJsHeapSizeLimit ::
    (MonadIO m) =>
    Ptr () ->                               -- self
    m Word64
dOMMemoryInfoGetJsHeapSizeLimit self = liftIO $ do
    result <- webkit_dom_memory_info_get_js_heap_size_limit self
    return result

-- method DOMMemoryInfo::get_total_js_heap_size
-- method type : MemberFunction
-- Args : [Arg {argName = "self", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "self", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt64
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_memory_info_get_total_js_heap_size" webkit_dom_memory_info_get_total_js_heap_size :: 
    Ptr () ->                               -- self : TBasicType TVoid
    IO Word64

{-# DEPRECATED dOMMemoryInfoGetTotalJsHeapSize ["(Since version 2.2)"]#-}
dOMMemoryInfoGetTotalJsHeapSize ::
    (MonadIO m) =>
    Ptr () ->                               -- self
    m Word64
dOMMemoryInfoGetTotalJsHeapSize self = liftIO $ do
    result <- webkit_dom_memory_info_get_total_js_heap_size self
    return result

-- method DOMMemoryInfo::get_used_js_heap_size
-- method type : MemberFunction
-- Args : [Arg {argName = "self", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "self", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt64
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_memory_info_get_used_js_heap_size" webkit_dom_memory_info_get_used_js_heap_size :: 
    Ptr () ->                               -- self : TBasicType TVoid
    IO Word64

{-# DEPRECATED dOMMemoryInfoGetUsedJsHeapSize ["(Since version 2.2)"]#-}
dOMMemoryInfoGetUsedJsHeapSize ::
    (MonadIO m) =>
    Ptr () ->                               -- self
    m Word64
dOMMemoryInfoGetUsedJsHeapSize self = liftIO $ do
    result <- webkit_dom_memory_info_get_used_js_heap_size self
    return result