{- |
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.DOMHistory
    ( 

-- * Exported types
    DOMHistory(..)                          ,
    DOMHistoryK                             ,
    toDOMHistory                            ,
    noDOMHistory                            ,


 -- * Methods
-- ** dOMHistoryBack
    dOMHistoryBack                          ,


-- ** dOMHistoryForward
    dOMHistoryForward                       ,


-- ** dOMHistoryGetLength
    dOMHistoryGetLength                     ,


-- ** dOMHistoryGo
    dOMHistoryGo                            ,




 -- * Properties
-- ** Length
    DOMHistoryLengthPropertyInfo            ,
    getDOMHistoryLength                     ,




    ) 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 DOMHistory = DOMHistory (ForeignPtr DOMHistory)
foreign import ccall "webkit_dom_history_get_type"
    c_webkit_dom_history_get_type :: IO GType

type instance ParentTypes DOMHistory = DOMHistoryParentTypes
type DOMHistoryParentTypes = '[DOMObject, GObject.Object]

instance GObject DOMHistory where
    gobjectIsInitiallyUnowned _ = False
    gobjectType _ = c_webkit_dom_history_get_type
    

class GObject o => DOMHistoryK o
instance (GObject o, IsDescendantOf DOMHistory o) => DOMHistoryK o

toDOMHistory :: DOMHistoryK o => o -> IO DOMHistory
toDOMHistory = unsafeCastTo DOMHistory

noDOMHistory :: Maybe DOMHistory
noDOMHistory = Nothing

-- VVV Prop "length"
   -- Type: TBasicType TUInt64
   -- Flags: [PropertyReadable]

getDOMHistoryLength :: (MonadIO m, DOMHistoryK o) => o -> m Word64
getDOMHistoryLength obj = liftIO $ getObjectPropertyUInt64 obj "length"

data DOMHistoryLengthPropertyInfo
instance AttrInfo DOMHistoryLengthPropertyInfo where
    type AttrAllowedOps DOMHistoryLengthPropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint DOMHistoryLengthPropertyInfo = (~) ()
    type AttrBaseTypeConstraint DOMHistoryLengthPropertyInfo = DOMHistoryK
    type AttrGetType DOMHistoryLengthPropertyInfo = Word64
    type AttrLabel DOMHistoryLengthPropertyInfo = "DOMHistory::length"
    attrGet _ = getDOMHistoryLength
    attrSet _ = undefined
    attrConstruct _ = undefined

type instance AttributeList DOMHistory = DOMHistoryAttributeList
type DOMHistoryAttributeList = ('[ '("core-object", DOMObjectCoreObjectPropertyInfo), '("length", DOMHistoryLengthPropertyInfo)] :: [(Symbol, *)])

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

-- method DOMHistory::back
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHistory", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHistory", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_history_back" webkit_dom_history_back :: 
    Ptr DOMHistory ->                       -- _obj : TInterface "WebKit" "DOMHistory"
    IO ()


dOMHistoryBack ::
    (MonadIO m, DOMHistoryK a) =>
    a ->                                    -- _obj
    m ()
dOMHistoryBack _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    webkit_dom_history_back _obj'
    touchManagedPtr _obj
    return ()

-- method DOMHistory::forward
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHistory", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHistory", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_history_forward" webkit_dom_history_forward :: 
    Ptr DOMHistory ->                       -- _obj : TInterface "WebKit" "DOMHistory"
    IO ()


dOMHistoryForward ::
    (MonadIO m, DOMHistoryK a) =>
    a ->                                    -- _obj
    m ()
dOMHistoryForward _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    webkit_dom_history_forward _obj'
    touchManagedPtr _obj
    return ()

-- method DOMHistory::get_length
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHistory", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHistory", 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_history_get_length" webkit_dom_history_get_length :: 
    Ptr DOMHistory ->                       -- _obj : TInterface "WebKit" "DOMHistory"
    IO Word64


dOMHistoryGetLength ::
    (MonadIO m, DOMHistoryK a) =>
    a ->                                    -- _obj
    m Word64
dOMHistoryGetLength _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- webkit_dom_history_get_length _obj'
    touchManagedPtr _obj
    return result

-- method DOMHistory::go
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHistory", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "distance", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "WebKit" "DOMHistory", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "distance", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "webkit_dom_history_go" webkit_dom_history_go :: 
    Ptr DOMHistory ->                       -- _obj : TInterface "WebKit" "DOMHistory"
    Int64 ->                                -- distance : TBasicType TInt64
    IO ()


dOMHistoryGo ::
    (MonadIO m, DOMHistoryK a) =>
    a ->                                    -- _obj
    Int64 ->                                -- distance
    m ()
dOMHistoryGo _obj distance = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    webkit_dom_history_go _obj' distance
    touchManagedPtr _obj
    return ()