{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A @GdkPopup@ is a surface that is attached to another surface.
-- 
-- The @GdkPopup@ is positioned relative to its parent surface.
-- 
-- @GdkPopup@s are typically used to implement menus and similar popups.
-- They can be modal, which is indicated by the [property/@gdkPopup@/:autohide]
-- property.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Gdk.Interfaces.Popup
    ( 

-- * Exported types
    Popup(..)                               ,
    IsPopup                                 ,
    toPopup                                 ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [beep]("GI.Gdk.Objects.Surface#g:method:beep"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [createCairoContext]("GI.Gdk.Objects.Surface#g:method:createCairoContext"), [createGlContext]("GI.Gdk.Objects.Surface#g:method:createGlContext"), [createSimilarSurface]("GI.Gdk.Objects.Surface#g:method:createSimilarSurface"), [createVulkanContext]("GI.Gdk.Objects.Surface#g:method:createVulkanContext"), [destroy]("GI.Gdk.Objects.Surface#g:method:destroy"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [hide]("GI.Gdk.Objects.Surface#g:method:hide"), [isDestroyed]("GI.Gdk.Objects.Surface#g:method:isDestroyed"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [present]("GI.Gdk.Interfaces.Popup#g:method:present"), [queueRender]("GI.Gdk.Objects.Surface#g:method:queueRender"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [requestLayout]("GI.Gdk.Objects.Surface#g:method:requestLayout"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [translateCoordinates]("GI.Gdk.Objects.Surface#g:method:translateCoordinates"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAutohide]("GI.Gdk.Interfaces.Popup#g:method:getAutohide"), [getCursor]("GI.Gdk.Objects.Surface#g:method:getCursor"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDeviceCursor]("GI.Gdk.Objects.Surface#g:method:getDeviceCursor"), [getDevicePosition]("GI.Gdk.Objects.Surface#g:method:getDevicePosition"), [getDisplay]("GI.Gdk.Objects.Surface#g:method:getDisplay"), [getFrameClock]("GI.Gdk.Objects.Surface#g:method:getFrameClock"), [getHeight]("GI.Gdk.Objects.Surface#g:method:getHeight"), [getMapped]("GI.Gdk.Objects.Surface#g:method:getMapped"), [getParent]("GI.Gdk.Interfaces.Popup#g:method:getParent"), [getPositionX]("GI.Gdk.Interfaces.Popup#g:method:getPositionX"), [getPositionY]("GI.Gdk.Interfaces.Popup#g:method:getPositionY"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRectAnchor]("GI.Gdk.Interfaces.Popup#g:method:getRectAnchor"), [getScaleFactor]("GI.Gdk.Objects.Surface#g:method:getScaleFactor"), [getSurfaceAnchor]("GI.Gdk.Interfaces.Popup#g:method:getSurfaceAnchor"), [getWidth]("GI.Gdk.Objects.Surface#g:method:getWidth").
-- 
-- ==== Setters
-- [setCursor]("GI.Gdk.Objects.Surface#g:method:setCursor"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDeviceCursor]("GI.Gdk.Objects.Surface#g:method:setDeviceCursor"), [setInputRegion]("GI.Gdk.Objects.Surface#g:method:setInputRegion"), [setOpaqueRegion]("GI.Gdk.Objects.Surface#g:method:setOpaqueRegion"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolvePopupMethod                      ,
#endif

-- ** getAutohide #method:getAutohide#

#if defined(ENABLE_OVERLOADING)
    PopupGetAutohideMethodInfo              ,
#endif
    popupGetAutohide                        ,


-- ** getParent #method:getParent#

#if defined(ENABLE_OVERLOADING)
    PopupGetParentMethodInfo                ,
#endif
    popupGetParent                          ,


-- ** getPositionX #method:getPositionX#

#if defined(ENABLE_OVERLOADING)
    PopupGetPositionXMethodInfo             ,
#endif
    popupGetPositionX                       ,


-- ** getPositionY #method:getPositionY#

#if defined(ENABLE_OVERLOADING)
    PopupGetPositionYMethodInfo             ,
#endif
    popupGetPositionY                       ,


-- ** getRectAnchor #method:getRectAnchor#

#if defined(ENABLE_OVERLOADING)
    PopupGetRectAnchorMethodInfo            ,
#endif
    popupGetRectAnchor                      ,


-- ** getSurfaceAnchor #method:getSurfaceAnchor#

#if defined(ENABLE_OVERLOADING)
    PopupGetSurfaceAnchorMethodInfo         ,
#endif
    popupGetSurfaceAnchor                   ,


-- ** present #method:present#

#if defined(ENABLE_OVERLOADING)
    PopupPresentMethodInfo                  ,
#endif
    popupPresent                            ,




 -- * Properties


-- ** autohide #attr:autohide#
-- | Whether to hide on outside clicks.

#if defined(ENABLE_OVERLOADING)
    PopupAutohidePropertyInfo               ,
#endif
    constructPopupAutohide                  ,
    getPopupAutohide                        ,
#if defined(ENABLE_OVERLOADING)
    popupAutohide                           ,
#endif


-- ** parent #attr:parent#
-- | The parent surface.

#if defined(ENABLE_OVERLOADING)
    PopupParentPropertyInfo                 ,
#endif
    constructPopupParent                    ,
    getPopupParent                          ,
#if defined(ENABLE_OVERLOADING)
    popupParent                             ,
#endif




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Objects.Surface as Gdk.Surface
import {-# SOURCE #-} qualified GI.Gdk.Structs.PopupLayout as Gdk.PopupLayout

-- interface Popup 
-- | Memory-managed wrapper type.
newtype Popup = Popup (SP.ManagedPtr Popup)
    deriving (Popup -> Popup -> Bool
(Popup -> Popup -> Bool) -> (Popup -> Popup -> Bool) -> Eq Popup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Popup -> Popup -> Bool
== :: Popup -> Popup -> Bool
$c/= :: Popup -> Popup -> Bool
/= :: Popup -> Popup -> Bool
Eq)

instance SP.ManagedPtrNewtype Popup where
    toManagedPtr :: Popup -> ManagedPtr Popup
toManagedPtr (Popup ManagedPtr Popup
p) = ManagedPtr Popup
p

foreign import ccall "gdk_popup_get_type"
    c_gdk_popup_get_type :: IO B.Types.GType

instance B.Types.TypedObject Popup where
    glibType :: IO GType
glibType = IO GType
c_gdk_popup_get_type

instance B.Types.GObject Popup

-- | Type class for types which can be safely cast to `Popup`, for instance with `toPopup`.
class (SP.GObject o, O.IsDescendantOf Popup o) => IsPopup o
instance (SP.GObject o, O.IsDescendantOf Popup o) => IsPopup o

instance O.HasParentTypes Popup
type instance O.ParentTypes Popup = '[GObject.Object.Object, Gdk.Surface.Surface]

-- | Cast to `Popup`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toPopup :: (MIO.MonadIO m, IsPopup o) => o -> m Popup
toPopup :: forall (m :: * -> *) o. (MonadIO m, IsPopup o) => o -> m Popup
toPopup = IO Popup -> m Popup
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Popup -> m Popup) -> (o -> IO Popup) -> o -> m Popup
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Popup -> Popup) -> o -> IO Popup
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Popup -> Popup
Popup

-- | Convert 'Popup' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe Popup) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_popup_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Popup -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Popup
P.Nothing = Ptr GValue -> Ptr Popup -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Popup
forall a. Ptr a
FP.nullPtr :: FP.Ptr Popup)
    gvalueSet_ Ptr GValue
gv (P.Just Popup
obj) = Popup -> (Ptr Popup -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Popup
obj (Ptr GValue -> Ptr Popup -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Popup)
gvalueGet_ Ptr GValue
gv = do
        Ptr Popup
ptr <- Ptr GValue -> IO (Ptr Popup)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Popup)
        if Ptr Popup
ptr Ptr Popup -> Ptr Popup -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Popup
forall a. Ptr a
FP.nullPtr
        then Popup -> Maybe Popup
forall a. a -> Maybe a
P.Just (Popup -> Maybe Popup) -> IO Popup -> IO (Maybe Popup)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Popup -> Popup) -> Ptr Popup -> IO Popup
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Popup -> Popup
Popup Ptr Popup
ptr
        else Maybe Popup -> IO (Maybe Popup)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Popup
forall a. Maybe a
P.Nothing
        
    

-- VVV Prop "autohide"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@autohide@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' popup #autohide
-- @
getPopupAutohide :: (MonadIO m, IsPopup o) => o -> m Bool
getPopupAutohide :: forall (m :: * -> *) o. (MonadIO m, IsPopup o) => o -> m Bool
getPopupAutohide o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"autohide"

-- | Construct a `GValueConstruct` with valid value for the “@autohide@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPopupAutohide :: (IsPopup o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPopupAutohide :: forall o (m :: * -> *).
(IsPopup o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructPopupAutohide Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"autohide" Bool
val

#if defined(ENABLE_OVERLOADING)
data PopupAutohidePropertyInfo
instance AttrInfo PopupAutohidePropertyInfo where
    type AttrAllowedOps PopupAutohidePropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PopupAutohidePropertyInfo = IsPopup
    type AttrSetTypeConstraint PopupAutohidePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint PopupAutohidePropertyInfo = (~) Bool
    type AttrTransferType PopupAutohidePropertyInfo = Bool
    type AttrGetType PopupAutohidePropertyInfo = Bool
    type AttrLabel PopupAutohidePropertyInfo = "autohide"
    type AttrOrigin PopupAutohidePropertyInfo = Popup
    attrGet = getPopupAutohide
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructPopupAutohide
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Interfaces.Popup.autohide"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Interfaces-Popup.html#g:attr:autohide"
        })
#endif

-- VVV Prop "parent"
   -- Type: TInterface (Name {namespace = "Gdk", name = "Surface"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just True,Nothing)

-- | Get the value of the “@parent@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' popup #parent
-- @
getPopupParent :: (MonadIO m, IsPopup o) => o -> m (Maybe Gdk.Surface.Surface)
getPopupParent :: forall (m :: * -> *) o.
(MonadIO m, IsPopup o) =>
o -> m (Maybe Surface)
getPopupParent o
obj = IO (Maybe Surface) -> m (Maybe Surface)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Surface) -> m (Maybe Surface))
-> IO (Maybe Surface) -> m (Maybe Surface)
forall a b. (a -> b) -> a -> b
$ o
-> String -> (ManagedPtr Surface -> Surface) -> IO (Maybe Surface)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"parent" ManagedPtr Surface -> Surface
Gdk.Surface.Surface

-- | Construct a `GValueConstruct` with valid value for the “@parent@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPopupParent :: (IsPopup o, MIO.MonadIO m, Gdk.Surface.IsSurface a) => a -> m (GValueConstruct o)
constructPopupParent :: forall o (m :: * -> *) a.
(IsPopup o, MonadIO m, IsSurface a) =>
a -> m (GValueConstruct o)
constructPopupParent a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"parent" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data PopupParentPropertyInfo
instance AttrInfo PopupParentPropertyInfo where
    type AttrAllowedOps PopupParentPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint PopupParentPropertyInfo = IsPopup
    type AttrSetTypeConstraint PopupParentPropertyInfo = Gdk.Surface.IsSurface
    type AttrTransferTypeConstraint PopupParentPropertyInfo = Gdk.Surface.IsSurface
    type AttrTransferType PopupParentPropertyInfo = Gdk.Surface.Surface
    type AttrGetType PopupParentPropertyInfo = (Maybe Gdk.Surface.Surface)
    type AttrLabel PopupParentPropertyInfo = "parent"
    type AttrOrigin PopupParentPropertyInfo = Popup
    attrGet = getPopupParent
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gdk.Surface.Surface v
    attrConstruct = constructPopupParent
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Interfaces.Popup.parent"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Interfaces-Popup.html#g:attr:parent"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Popup
type instance O.AttributeList Popup = PopupAttributeList
type PopupAttributeList = ('[ '("autohide", PopupAutohidePropertyInfo), '("cursor", Gdk.Surface.SurfaceCursorPropertyInfo), '("display", Gdk.Surface.SurfaceDisplayPropertyInfo), '("frameClock", Gdk.Surface.SurfaceFrameClockPropertyInfo), '("height", Gdk.Surface.SurfaceHeightPropertyInfo), '("mapped", Gdk.Surface.SurfaceMappedPropertyInfo), '("parent", PopupParentPropertyInfo), '("scaleFactor", Gdk.Surface.SurfaceScaleFactorPropertyInfo), '("width", Gdk.Surface.SurfaceWidthPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
popupAutohide :: AttrLabelProxy "autohide"
popupAutohide = AttrLabelProxy

popupParent :: AttrLabelProxy "parent"
popupParent = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolvePopupMethod (t :: Symbol) (o :: *) :: * where
    ResolvePopupMethod "beep" o = Gdk.Surface.SurfaceBeepMethodInfo
    ResolvePopupMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolvePopupMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolvePopupMethod "createCairoContext" o = Gdk.Surface.SurfaceCreateCairoContextMethodInfo
    ResolvePopupMethod "createGlContext" o = Gdk.Surface.SurfaceCreateGlContextMethodInfo
    ResolvePopupMethod "createSimilarSurface" o = Gdk.Surface.SurfaceCreateSimilarSurfaceMethodInfo
    ResolvePopupMethod "createVulkanContext" o = Gdk.Surface.SurfaceCreateVulkanContextMethodInfo
    ResolvePopupMethod "destroy" o = Gdk.Surface.SurfaceDestroyMethodInfo
    ResolvePopupMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolvePopupMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolvePopupMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolvePopupMethod "hide" o = Gdk.Surface.SurfaceHideMethodInfo
    ResolvePopupMethod "isDestroyed" o = Gdk.Surface.SurfaceIsDestroyedMethodInfo
    ResolvePopupMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolvePopupMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolvePopupMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolvePopupMethod "present" o = PopupPresentMethodInfo
    ResolvePopupMethod "queueRender" o = Gdk.Surface.SurfaceQueueRenderMethodInfo
    ResolvePopupMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolvePopupMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolvePopupMethod "requestLayout" o = Gdk.Surface.SurfaceRequestLayoutMethodInfo
    ResolvePopupMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolvePopupMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolvePopupMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolvePopupMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolvePopupMethod "translateCoordinates" o = Gdk.Surface.SurfaceTranslateCoordinatesMethodInfo
    ResolvePopupMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolvePopupMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolvePopupMethod "getAutohide" o = PopupGetAutohideMethodInfo
    ResolvePopupMethod "getCursor" o = Gdk.Surface.SurfaceGetCursorMethodInfo
    ResolvePopupMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolvePopupMethod "getDeviceCursor" o = Gdk.Surface.SurfaceGetDeviceCursorMethodInfo
    ResolvePopupMethod "getDevicePosition" o = Gdk.Surface.SurfaceGetDevicePositionMethodInfo
    ResolvePopupMethod "getDisplay" o = Gdk.Surface.SurfaceGetDisplayMethodInfo
    ResolvePopupMethod "getFrameClock" o = Gdk.Surface.SurfaceGetFrameClockMethodInfo
    ResolvePopupMethod "getHeight" o = Gdk.Surface.SurfaceGetHeightMethodInfo
    ResolvePopupMethod "getMapped" o = Gdk.Surface.SurfaceGetMappedMethodInfo
    ResolvePopupMethod "getParent" o = PopupGetParentMethodInfo
    ResolvePopupMethod "getPositionX" o = PopupGetPositionXMethodInfo
    ResolvePopupMethod "getPositionY" o = PopupGetPositionYMethodInfo
    ResolvePopupMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolvePopupMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolvePopupMethod "getRectAnchor" o = PopupGetRectAnchorMethodInfo
    ResolvePopupMethod "getScaleFactor" o = Gdk.Surface.SurfaceGetScaleFactorMethodInfo
    ResolvePopupMethod "getSurfaceAnchor" o = PopupGetSurfaceAnchorMethodInfo
    ResolvePopupMethod "getWidth" o = Gdk.Surface.SurfaceGetWidthMethodInfo
    ResolvePopupMethod "setCursor" o = Gdk.Surface.SurfaceSetCursorMethodInfo
    ResolvePopupMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolvePopupMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolvePopupMethod "setDeviceCursor" o = Gdk.Surface.SurfaceSetDeviceCursorMethodInfo
    ResolvePopupMethod "setInputRegion" o = Gdk.Surface.SurfaceSetInputRegionMethodInfo
    ResolvePopupMethod "setOpaqueRegion" o = Gdk.Surface.SurfaceSetOpaqueRegionMethodInfo
    ResolvePopupMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolvePopupMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolvePopupMethod t Popup, O.OverloadedMethod info Popup p) => OL.IsLabel t (Popup -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolvePopupMethod t Popup, O.OverloadedMethod info Popup p, R.HasField t Popup p) => R.HasField t Popup p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolvePopupMethod t Popup, O.OverloadedMethodInfo info Popup) => OL.IsLabel t (O.MethodProxy info Popup) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- method Popup::get_autohide
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "popup"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Popup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkPopup`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_popup_get_autohide" gdk_popup_get_autohide :: 
    Ptr Popup ->                            -- popup : TInterface (Name {namespace = "Gdk", name = "Popup"})
    IO CInt

-- | Returns whether this popup is set to hide on outside clicks.
popupGetAutohide ::
    (B.CallStack.HasCallStack, MonadIO m, IsPopup a) =>
    a
    -- ^ /@popup@/: a @GdkPopup@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@popup@/ will autohide
popupGetAutohide :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPopup a) =>
a -> m Bool
popupGetAutohide a
popup = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Popup
popup' <- a -> IO (Ptr Popup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
popup
    CInt
result <- Ptr Popup -> IO CInt
gdk_popup_get_autohide Ptr Popup
popup'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
popup
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PopupGetAutohideMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPopup a) => O.OverloadedMethod PopupGetAutohideMethodInfo a signature where
    overloadedMethod = popupGetAutohide

instance O.OverloadedMethodInfo PopupGetAutohideMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Interfaces.Popup.popupGetAutohide",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Interfaces-Popup.html#v:popupGetAutohide"
        })


#endif

-- method Popup::get_parent
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "popup"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Popup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkPopup`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Surface" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_popup_get_parent" gdk_popup_get_parent :: 
    Ptr Popup ->                            -- popup : TInterface (Name {namespace = "Gdk", name = "Popup"})
    IO (Ptr Gdk.Surface.Surface)

-- | Returns the parent surface of a popup.
popupGetParent ::
    (B.CallStack.HasCallStack, MonadIO m, IsPopup a) =>
    a
    -- ^ /@popup@/: a @GdkPopup@
    -> m (Maybe Gdk.Surface.Surface)
    -- ^ __Returns:__ the parent surface
popupGetParent :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPopup a) =>
a -> m (Maybe Surface)
popupGetParent a
popup = IO (Maybe Surface) -> m (Maybe Surface)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Surface) -> m (Maybe Surface))
-> IO (Maybe Surface) -> m (Maybe Surface)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Popup
popup' <- a -> IO (Ptr Popup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
popup
    Ptr Surface
result <- Ptr Popup -> IO (Ptr Surface)
gdk_popup_get_parent Ptr Popup
popup'
    Maybe Surface
maybeResult <- Ptr Surface -> (Ptr Surface -> IO Surface) -> IO (Maybe Surface)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Surface
result ((Ptr Surface -> IO Surface) -> IO (Maybe Surface))
-> (Ptr Surface -> IO Surface) -> IO (Maybe Surface)
forall a b. (a -> b) -> a -> b
$ \Ptr Surface
result' -> do
        Surface
result'' <- ((ManagedPtr Surface -> Surface) -> Ptr Surface -> IO Surface
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Surface -> Surface
Gdk.Surface.Surface) Ptr Surface
result'
        Surface -> IO Surface
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Surface
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
popup
    Maybe Surface -> IO (Maybe Surface)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Surface
maybeResult

#if defined(ENABLE_OVERLOADING)
data PopupGetParentMethodInfo
instance (signature ~ (m (Maybe Gdk.Surface.Surface)), MonadIO m, IsPopup a) => O.OverloadedMethod PopupGetParentMethodInfo a signature where
    overloadedMethod = popupGetParent

instance O.OverloadedMethodInfo PopupGetParentMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Interfaces.Popup.popupGetParent",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Interfaces-Popup.html#v:popupGetParent"
        })


#endif

-- method Popup::get_position_x
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "popup"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Popup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkPopup`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_popup_get_position_x" gdk_popup_get_position_x :: 
    Ptr Popup ->                            -- popup : TInterface (Name {namespace = "Gdk", name = "Popup"})
    IO Int32

-- | Obtains the position of the popup relative to its parent.
popupGetPositionX ::
    (B.CallStack.HasCallStack, MonadIO m, IsPopup a) =>
    a
    -- ^ /@popup@/: a @GdkPopup@
    -> m Int32
    -- ^ __Returns:__ the X coordinate of /@popup@/ position
popupGetPositionX :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPopup a) =>
a -> m Int32
popupGetPositionX a
popup = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Popup
popup' <- a -> IO (Ptr Popup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
popup
    Int32
result <- Ptr Popup -> IO Int32
gdk_popup_get_position_x Ptr Popup
popup'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
popup
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data PopupGetPositionXMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsPopup a) => O.OverloadedMethod PopupGetPositionXMethodInfo a signature where
    overloadedMethod = popupGetPositionX

instance O.OverloadedMethodInfo PopupGetPositionXMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Interfaces.Popup.popupGetPositionX",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Interfaces-Popup.html#v:popupGetPositionX"
        })


#endif

-- method Popup::get_position_y
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "popup"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Popup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkPopup`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_popup_get_position_y" gdk_popup_get_position_y :: 
    Ptr Popup ->                            -- popup : TInterface (Name {namespace = "Gdk", name = "Popup"})
    IO Int32

-- | Obtains the position of the popup relative to its parent.
popupGetPositionY ::
    (B.CallStack.HasCallStack, MonadIO m, IsPopup a) =>
    a
    -- ^ /@popup@/: a @GdkPopup@
    -> m Int32
    -- ^ __Returns:__ the Y coordinate of /@popup@/ position
popupGetPositionY :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPopup a) =>
a -> m Int32
popupGetPositionY a
popup = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Popup
popup' <- a -> IO (Ptr Popup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
popup
    Int32
result <- Ptr Popup -> IO Int32
gdk_popup_get_position_y Ptr Popup
popup'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
popup
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data PopupGetPositionYMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsPopup a) => O.OverloadedMethod PopupGetPositionYMethodInfo a signature where
    overloadedMethod = popupGetPositionY

instance O.OverloadedMethodInfo PopupGetPositionYMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Interfaces.Popup.popupGetPositionY",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Interfaces-Popup.html#v:popupGetPositionY"
        })


#endif

-- method Popup::get_rect_anchor
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "popup"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Popup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkPopup`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Gravity" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_popup_get_rect_anchor" gdk_popup_get_rect_anchor :: 
    Ptr Popup ->                            -- popup : TInterface (Name {namespace = "Gdk", name = "Popup"})
    IO CUInt

-- | Gets the current popup rectangle anchor.
-- 
-- The value returned may change after calling 'GI.Gdk.Interfaces.Popup.popupPresent',
-- or after the [Surface::layout]("GI.Gdk.Objects.Surface#g:signal:layout") signal is emitted.
popupGetRectAnchor ::
    (B.CallStack.HasCallStack, MonadIO m, IsPopup a) =>
    a
    -- ^ /@popup@/: a @GdkPopup@
    -> m Gdk.Enums.Gravity
    -- ^ __Returns:__ the current rectangle anchor value of /@popup@/
popupGetRectAnchor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPopup a) =>
a -> m Gravity
popupGetRectAnchor a
popup = IO Gravity -> m Gravity
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Gravity -> m Gravity) -> IO Gravity -> m Gravity
forall a b. (a -> b) -> a -> b
$ do
    Ptr Popup
popup' <- a -> IO (Ptr Popup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
popup
    CUInt
result <- Ptr Popup -> IO CUInt
gdk_popup_get_rect_anchor Ptr Popup
popup'
    let result' :: Gravity
result' = (Int -> Gravity
forall a. Enum a => Int -> a
toEnum (Int -> Gravity) -> (CUInt -> Int) -> CUInt -> Gravity
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
popup
    Gravity -> IO Gravity
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Gravity
result'

#if defined(ENABLE_OVERLOADING)
data PopupGetRectAnchorMethodInfo
instance (signature ~ (m Gdk.Enums.Gravity), MonadIO m, IsPopup a) => O.OverloadedMethod PopupGetRectAnchorMethodInfo a signature where
    overloadedMethod = popupGetRectAnchor

instance O.OverloadedMethodInfo PopupGetRectAnchorMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Interfaces.Popup.popupGetRectAnchor",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Interfaces-Popup.html#v:popupGetRectAnchor"
        })


#endif

-- method Popup::get_surface_anchor
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "popup"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Popup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkPopup`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Gravity" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_popup_get_surface_anchor" gdk_popup_get_surface_anchor :: 
    Ptr Popup ->                            -- popup : TInterface (Name {namespace = "Gdk", name = "Popup"})
    IO CUInt

-- | Gets the current popup surface anchor.
-- 
-- The value returned may change after calling 'GI.Gdk.Interfaces.Popup.popupPresent',
-- or after the [Surface::layout]("GI.Gdk.Objects.Surface#g:signal:layout") signal is emitted.
popupGetSurfaceAnchor ::
    (B.CallStack.HasCallStack, MonadIO m, IsPopup a) =>
    a
    -- ^ /@popup@/: a @GdkPopup@
    -> m Gdk.Enums.Gravity
    -- ^ __Returns:__ the current surface anchor value of /@popup@/
popupGetSurfaceAnchor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPopup a) =>
a -> m Gravity
popupGetSurfaceAnchor a
popup = IO Gravity -> m Gravity
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Gravity -> m Gravity) -> IO Gravity -> m Gravity
forall a b. (a -> b) -> a -> b
$ do
    Ptr Popup
popup' <- a -> IO (Ptr Popup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
popup
    CUInt
result <- Ptr Popup -> IO CUInt
gdk_popup_get_surface_anchor Ptr Popup
popup'
    let result' :: Gravity
result' = (Int -> Gravity
forall a. Enum a => Int -> a
toEnum (Int -> Gravity) -> (CUInt -> Int) -> CUInt -> Gravity
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
popup
    Gravity -> IO Gravity
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Gravity
result'

#if defined(ENABLE_OVERLOADING)
data PopupGetSurfaceAnchorMethodInfo
instance (signature ~ (m Gdk.Enums.Gravity), MonadIO m, IsPopup a) => O.OverloadedMethod PopupGetSurfaceAnchorMethodInfo a signature where
    overloadedMethod = popupGetSurfaceAnchor

instance O.OverloadedMethodInfo PopupGetSurfaceAnchorMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Interfaces.Popup.popupGetSurfaceAnchor",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Interfaces-Popup.html#v:popupGetSurfaceAnchor"
        })


#endif

-- method Popup::present
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "popup"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Popup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the `GdkPopup` to show"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the unconstrained popup width to layout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the unconstrained popup height to layout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "PopupLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the `GdkPopupLayout` object used to layout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_popup_present" gdk_popup_present :: 
    Ptr Popup ->                            -- popup : TInterface (Name {namespace = "Gdk", name = "Popup"})
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    Ptr Gdk.PopupLayout.PopupLayout ->      -- layout : TInterface (Name {namespace = "Gdk", name = "PopupLayout"})
    IO CInt

-- | Present /@popup@/ after having processed the @GdkPopupLayout@ rules.
-- 
-- If the popup was previously now showing, it will be showed,
-- otherwise it will change position according to /@layout@/.
-- 
-- After calling this function, the result should be handled in response
-- to the [signal/@gdkSurface@/[layout](#g:signal:layout)] signal being emitted. The resulting
-- popup position can be queried using 'GI.Gdk.Interfaces.Popup.popupGetPositionX',
-- 'GI.Gdk.Interfaces.Popup.popupGetPositionY', and the resulting size will be sent as
-- parameters in the layout signal. Use 'GI.Gdk.Interfaces.Popup.popupGetRectAnchor'
-- and 'GI.Gdk.Interfaces.Popup.popupGetSurfaceAnchor' to get the resulting anchors.
-- 
-- Presenting may fail, for example if the /@popup@/ is set to autohide
-- and is immediately hidden upon being presented. If presenting failed,
-- the [Surface::layout]("GI.Gdk.Objects.Surface#g:signal:layout") signal will not me emitted.
popupPresent ::
    (B.CallStack.HasCallStack, MonadIO m, IsPopup a) =>
    a
    -- ^ /@popup@/: the @GdkPopup@ to show
    -> Int32
    -- ^ /@width@/: the unconstrained popup width to layout
    -> Int32
    -- ^ /@height@/: the unconstrained popup height to layout
    -> Gdk.PopupLayout.PopupLayout
    -- ^ /@layout@/: the @GdkPopupLayout@ object used to layout
    -> m Bool
    -- ^ __Returns:__ 'P.False' if it failed to be presented, otherwise 'P.True'.
popupPresent :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPopup a) =>
a -> Int32 -> Int32 -> PopupLayout -> m Bool
popupPresent a
popup Int32
width Int32
height PopupLayout
layout = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Popup
popup' <- a -> IO (Ptr Popup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
popup
    Ptr PopupLayout
layout' <- PopupLayout -> IO (Ptr PopupLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PopupLayout
layout
    CInt
result <- Ptr Popup -> Int32 -> Int32 -> Ptr PopupLayout -> IO CInt
gdk_popup_present Ptr Popup
popup' Int32
width Int32
height Ptr PopupLayout
layout'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
popup
    PopupLayout -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PopupLayout
layout
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PopupPresentMethodInfo
instance (signature ~ (Int32 -> Int32 -> Gdk.PopupLayout.PopupLayout -> m Bool), MonadIO m, IsPopup a) => O.OverloadedMethod PopupPresentMethodInfo a signature where
    overloadedMethod = popupPresent

instance O.OverloadedMethodInfo PopupPresentMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Interfaces.Popup.popupPresent",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Interfaces-Popup.html#v:popupPresent"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Popup = PopupSignalList
type PopupSignalList = ('[ '("enterMonitor", Gdk.Surface.SurfaceEnterMonitorSignalInfo), '("event", Gdk.Surface.SurfaceEventSignalInfo), '("layout", Gdk.Surface.SurfaceLayoutSignalInfo), '("leaveMonitor", Gdk.Surface.SurfaceLeaveMonitorSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("render", Gdk.Surface.SurfaceRenderSignalInfo)] :: [(Symbol, *)])

#endif