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

An opaque structure used as the base of all interface types.
-}

module GI.GObject.Structs.TypeInterface
    ( 

-- * Exported types
    TypeInterface(..)                       ,
    noTypeInterface                         ,


 -- * Methods
-- ** typeInterfacePeekParent
    typeInterfacePeekParent                 ,




    ) 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.GObject.Types
import GI.GObject.Callbacks

newtype TypeInterface = TypeInterface (ForeignPtr TypeInterface)
noTypeInterface :: Maybe TypeInterface
noTypeInterface = Nothing

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

foreign import ccall "g_type_interface_peek_parent" g_type_interface_peek_parent :: 
    Ptr TypeInterface ->                    -- _obj : TInterface "GObject" "TypeInterface"
    IO (Ptr TypeInterface)


typeInterfacePeekParent ::
    (MonadIO m) =>
    TypeInterface ->                        -- _obj
    m TypeInterface
typeInterfacePeekParent _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_type_interface_peek_parent _obj'
    checkUnexpectedReturnNULL "g_type_interface_peek_parent" result
    result' <- (newPtr 16 TypeInterface) result
    touchManagedPtr _obj
    return result'