{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Structs.PopupLayout
(
PopupLayout(..) ,
#if defined(ENABLE_OVERLOADING)
ResolvePopupLayoutMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
PopupLayoutCopyMethodInfo ,
#endif
popupLayoutCopy ,
#if defined(ENABLE_OVERLOADING)
PopupLayoutEqualMethodInfo ,
#endif
popupLayoutEqual ,
#if defined(ENABLE_OVERLOADING)
PopupLayoutGetAnchorHintsMethodInfo ,
#endif
popupLayoutGetAnchorHints ,
#if defined(ENABLE_OVERLOADING)
PopupLayoutGetAnchorRectMethodInfo ,
#endif
popupLayoutGetAnchorRect ,
#if defined(ENABLE_OVERLOADING)
PopupLayoutGetOffsetMethodInfo ,
#endif
popupLayoutGetOffset ,
#if defined(ENABLE_OVERLOADING)
PopupLayoutGetRectAnchorMethodInfo ,
#endif
popupLayoutGetRectAnchor ,
#if defined(ENABLE_OVERLOADING)
PopupLayoutGetSurfaceAnchorMethodInfo ,
#endif
popupLayoutGetSurfaceAnchor ,
popupLayoutNew ,
#if defined(ENABLE_OVERLOADING)
PopupLayoutRefMethodInfo ,
#endif
popupLayoutRef ,
#if defined(ENABLE_OVERLOADING)
PopupLayoutSetAnchorHintsMethodInfo ,
#endif
popupLayoutSetAnchorHints ,
#if defined(ENABLE_OVERLOADING)
PopupLayoutSetAnchorRectMethodInfo ,
#endif
popupLayoutSetAnchorRect ,
#if defined(ENABLE_OVERLOADING)
PopupLayoutSetOffsetMethodInfo ,
#endif
popupLayoutSetOffset ,
#if defined(ENABLE_OVERLOADING)
PopupLayoutSetRectAnchorMethodInfo ,
#endif
popupLayoutSetRectAnchor ,
#if defined(ENABLE_OVERLOADING)
PopupLayoutSetSurfaceAnchorMethodInfo ,
#endif
popupLayoutSetSurfaceAnchor ,
#if defined(ENABLE_OVERLOADING)
PopupLayoutUnrefMethodInfo ,
#endif
popupLayoutUnref ,
) 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.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
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.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 {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
newtype = (SP.ManagedPtr PopupLayout)
deriving (PopupLayout -> PopupLayout -> Bool
(PopupLayout -> PopupLayout -> Bool)
-> (PopupLayout -> PopupLayout -> Bool) -> Eq PopupLayout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PopupLayout -> PopupLayout -> Bool
$c/= :: PopupLayout -> PopupLayout -> Bool
== :: PopupLayout -> PopupLayout -> Bool
$c== :: PopupLayout -> PopupLayout -> Bool
Eq)
instance SP.ManagedPtrNewtype PopupLayout where
toManagedPtr :: PopupLayout -> ManagedPtr PopupLayout
toManagedPtr (PopupLayout ManagedPtr PopupLayout
p) = ManagedPtr PopupLayout
p
foreign import ccall "gdk_popup_layout_get_type" ::
IO GType
type instance O.ParentTypes PopupLayout = '[]
instance O.HasParentTypes PopupLayout
instance B.Types.TypedObject PopupLayout where
glibType :: IO GType
glibType = IO GType
c_gdk_popup_layout_get_type
instance B.Types.GBoxed PopupLayout
instance B.GValue.IsGValue PopupLayout where
toGValue :: PopupLayout -> IO GValue
toGValue PopupLayout
o = do
GType
gtype <- IO GType
c_gdk_popup_layout_get_type
PopupLayout -> (Ptr PopupLayout -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr PopupLayout
o (GType
-> (GValue -> Ptr PopupLayout -> IO ())
-> Ptr PopupLayout
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr PopupLayout -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
fromGValue :: GValue -> IO PopupLayout
fromGValue GValue
gv = do
Ptr PopupLayout
ptr <- GValue -> IO (Ptr PopupLayout)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr PopupLayout)
(ManagedPtr PopupLayout -> PopupLayout)
-> Ptr PopupLayout -> IO PopupLayout
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr PopupLayout -> PopupLayout
PopupLayout Ptr PopupLayout
ptr
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PopupLayout
type instance O.AttributeList PopupLayout = PopupLayoutAttributeList
type PopupLayoutAttributeList = ('[ ] :: [(Symbol, *)])
#endif
foreign import ccall "gdk_popup_layout_new" ::
Ptr Gdk.Rectangle.Rectangle ->
CUInt ->
CUInt ->
IO (Ptr PopupLayout)
popupLayoutNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
Gdk.Rectangle.Rectangle
-> Gdk.Enums.Gravity
-> Gdk.Enums.Gravity
-> m PopupLayout
Rectangle
anchorRect Gravity
rectAnchor Gravity
surfaceAnchor = IO PopupLayout -> m PopupLayout
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PopupLayout -> m PopupLayout)
-> IO PopupLayout -> m PopupLayout
forall a b. (a -> b) -> a -> b
$ do
Ptr Rectangle
anchorRect' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
anchorRect
let rectAnchor' :: CUInt
rectAnchor' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Gravity -> Int) -> Gravity -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Gravity -> Int
forall a. Enum a => a -> Int
fromEnum) Gravity
rectAnchor
let surfaceAnchor' :: CUInt
surfaceAnchor' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Gravity -> Int) -> Gravity -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Gravity -> Int
forall a. Enum a => a -> Int
fromEnum) Gravity
surfaceAnchor
Ptr PopupLayout
result <- Ptr Rectangle -> CUInt -> CUInt -> IO (Ptr PopupLayout)
gdk_popup_layout_new Ptr Rectangle
anchorRect' CUInt
rectAnchor' CUInt
surfaceAnchor'
Text -> Ptr PopupLayout -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"popupLayoutNew" Ptr PopupLayout
result
PopupLayout
result' <- ((ManagedPtr PopupLayout -> PopupLayout)
-> Ptr PopupLayout -> IO PopupLayout
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr PopupLayout -> PopupLayout
PopupLayout) Ptr PopupLayout
result
Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
anchorRect
PopupLayout -> IO PopupLayout
forall (m :: * -> *) a. Monad m => a -> m a
return PopupLayout
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gdk_popup_layout_copy" ::
Ptr PopupLayout ->
IO (Ptr PopupLayout)
popupLayoutCopy ::
(B.CallStack.HasCallStack, MonadIO m) =>
PopupLayout
-> m PopupLayout
PopupLayout
layout = IO PopupLayout -> m PopupLayout
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PopupLayout -> m PopupLayout)
-> IO PopupLayout -> m PopupLayout
forall a b. (a -> b) -> a -> b
$ do
Ptr PopupLayout
layout' <- PopupLayout -> IO (Ptr PopupLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PopupLayout
layout
Ptr PopupLayout
result <- Ptr PopupLayout -> IO (Ptr PopupLayout)
gdk_popup_layout_copy Ptr PopupLayout
layout'
Text -> Ptr PopupLayout -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"popupLayoutCopy" Ptr PopupLayout
result
PopupLayout
result' <- ((ManagedPtr PopupLayout -> PopupLayout)
-> Ptr PopupLayout -> IO PopupLayout
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr PopupLayout -> PopupLayout
PopupLayout) Ptr PopupLayout
result
PopupLayout -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PopupLayout
layout
PopupLayout -> IO PopupLayout
forall (m :: * -> *) a. Monad m => a -> m a
return PopupLayout
result'
#if defined(ENABLE_OVERLOADING)
data PopupLayoutCopyMethodInfo
instance (signature ~ (m PopupLayout), MonadIO m) => O.MethodInfo PopupLayoutCopyMethodInfo PopupLayout signature where
overloadedMethod = popupLayoutCopy
#endif
foreign import ccall "gdk_popup_layout_equal" ::
Ptr PopupLayout ->
Ptr PopupLayout ->
IO CInt
popupLayoutEqual ::
(B.CallStack.HasCallStack, MonadIO m) =>
PopupLayout
-> PopupLayout
-> m Bool
PopupLayout
layout PopupLayout
other = IO Bool -> m Bool
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 PopupLayout
layout' <- PopupLayout -> IO (Ptr PopupLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PopupLayout
layout
Ptr PopupLayout
other' <- PopupLayout -> IO (Ptr PopupLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PopupLayout
other
CInt
result <- Ptr PopupLayout -> Ptr PopupLayout -> IO CInt
gdk_popup_layout_equal Ptr PopupLayout
layout' Ptr PopupLayout
other'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
PopupLayout -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PopupLayout
layout
PopupLayout -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PopupLayout
other
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data PopupLayoutEqualMethodInfo
instance (signature ~ (PopupLayout -> m Bool), MonadIO m) => O.MethodInfo PopupLayoutEqualMethodInfo PopupLayout signature where
overloadedMethod = popupLayoutEqual
#endif
foreign import ccall "gdk_popup_layout_get_anchor_hints" ::
Ptr PopupLayout ->
IO CUInt
popupLayoutGetAnchorHints ::
(B.CallStack.HasCallStack, MonadIO m) =>
PopupLayout
-> m [Gdk.Flags.AnchorHints]
PopupLayout
layout = IO [AnchorHints] -> m [AnchorHints]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [AnchorHints] -> m [AnchorHints])
-> IO [AnchorHints] -> m [AnchorHints]
forall a b. (a -> b) -> a -> b
$ do
Ptr PopupLayout
layout' <- PopupLayout -> IO (Ptr PopupLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PopupLayout
layout
CUInt
result <- Ptr PopupLayout -> IO CUInt
gdk_popup_layout_get_anchor_hints Ptr PopupLayout
layout'
let result' :: [AnchorHints]
result' = CUInt -> [AnchorHints]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
PopupLayout -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PopupLayout
layout
[AnchorHints] -> IO [AnchorHints]
forall (m :: * -> *) a. Monad m => a -> m a
return [AnchorHints]
result'
#if defined(ENABLE_OVERLOADING)
data PopupLayoutGetAnchorHintsMethodInfo
instance (signature ~ (m [Gdk.Flags.AnchorHints]), MonadIO m) => O.MethodInfo PopupLayoutGetAnchorHintsMethodInfo PopupLayout signature where
overloadedMethod = popupLayoutGetAnchorHints
#endif
foreign import ccall "gdk_popup_layout_get_anchor_rect" ::
Ptr PopupLayout ->
IO (Ptr Gdk.Rectangle.Rectangle)
popupLayoutGetAnchorRect ::
(B.CallStack.HasCallStack, MonadIO m) =>
PopupLayout
-> m Gdk.Rectangle.Rectangle
PopupLayout
layout = IO Rectangle -> m Rectangle
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rectangle -> m Rectangle) -> IO Rectangle -> m Rectangle
forall a b. (a -> b) -> a -> b
$ do
Ptr PopupLayout
layout' <- PopupLayout -> IO (Ptr PopupLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PopupLayout
layout
Ptr Rectangle
result <- Ptr PopupLayout -> IO (Ptr Rectangle)
gdk_popup_layout_get_anchor_rect Ptr PopupLayout
layout'
Text -> Ptr Rectangle -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"popupLayoutGetAnchorRect" Ptr Rectangle
result
Rectangle
result' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Rectangle -> Rectangle
Gdk.Rectangle.Rectangle) Ptr Rectangle
result
PopupLayout -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PopupLayout
layout
Rectangle -> IO Rectangle
forall (m :: * -> *) a. Monad m => a -> m a
return Rectangle
result'
#if defined(ENABLE_OVERLOADING)
data PopupLayoutGetAnchorRectMethodInfo
instance (signature ~ (m Gdk.Rectangle.Rectangle), MonadIO m) => O.MethodInfo PopupLayoutGetAnchorRectMethodInfo PopupLayout signature where
overloadedMethod = popupLayoutGetAnchorRect
#endif
foreign import ccall "gdk_popup_layout_get_offset" ::
Ptr PopupLayout ->
Int32 ->
Int32 ->
IO ()
popupLayoutGetOffset ::
(B.CallStack.HasCallStack, MonadIO m) =>
PopupLayout
-> Int32
-> Int32
-> m ()
PopupLayout
layout Int32
dx Int32
dy = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr PopupLayout
layout' <- PopupLayout -> IO (Ptr PopupLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PopupLayout
layout
Ptr PopupLayout -> Int32 -> Int32 -> IO ()
gdk_popup_layout_get_offset Ptr PopupLayout
layout' Int32
dx Int32
dy
PopupLayout -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PopupLayout
layout
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PopupLayoutGetOffsetMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ()), MonadIO m) => O.MethodInfo PopupLayoutGetOffsetMethodInfo PopupLayout signature where
overloadedMethod = popupLayoutGetOffset
#endif
foreign import ccall "gdk_popup_layout_get_rect_anchor" ::
Ptr PopupLayout ->
IO CUInt
popupLayoutGetRectAnchor ::
(B.CallStack.HasCallStack, MonadIO m) =>
PopupLayout
-> m Gdk.Enums.Gravity
PopupLayout
layout = IO Gravity -> m Gravity
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 PopupLayout
layout' <- PopupLayout -> IO (Ptr PopupLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PopupLayout
layout
CUInt
result <- Ptr PopupLayout -> IO CUInt
gdk_popup_layout_get_rect_anchor Ptr PopupLayout
layout'
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
PopupLayout -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PopupLayout
layout
Gravity -> IO Gravity
forall (m :: * -> *) a. Monad m => a -> m a
return Gravity
result'
#if defined(ENABLE_OVERLOADING)
data PopupLayoutGetRectAnchorMethodInfo
instance (signature ~ (m Gdk.Enums.Gravity), MonadIO m) => O.MethodInfo PopupLayoutGetRectAnchorMethodInfo PopupLayout signature where
overloadedMethod = popupLayoutGetRectAnchor
#endif
foreign import ccall "gdk_popup_layout_get_surface_anchor" ::
Ptr PopupLayout ->
IO CUInt
popupLayoutGetSurfaceAnchor ::
(B.CallStack.HasCallStack, MonadIO m) =>
PopupLayout
-> m Gdk.Enums.Gravity
PopupLayout
layout = IO Gravity -> m Gravity
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 PopupLayout
layout' <- PopupLayout -> IO (Ptr PopupLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PopupLayout
layout
CUInt
result <- Ptr PopupLayout -> IO CUInt
gdk_popup_layout_get_surface_anchor Ptr PopupLayout
layout'
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
PopupLayout -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PopupLayout
layout
Gravity -> IO Gravity
forall (m :: * -> *) a. Monad m => a -> m a
return Gravity
result'
#if defined(ENABLE_OVERLOADING)
data PopupLayoutGetSurfaceAnchorMethodInfo
instance (signature ~ (m Gdk.Enums.Gravity), MonadIO m) => O.MethodInfo PopupLayoutGetSurfaceAnchorMethodInfo PopupLayout signature where
overloadedMethod = popupLayoutGetSurfaceAnchor
#endif
foreign import ccall "gdk_popup_layout_ref" ::
Ptr PopupLayout ->
IO (Ptr PopupLayout)
popupLayoutRef ::
(B.CallStack.HasCallStack, MonadIO m) =>
PopupLayout
-> m PopupLayout
PopupLayout
layout = IO PopupLayout -> m PopupLayout
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PopupLayout -> m PopupLayout)
-> IO PopupLayout -> m PopupLayout
forall a b. (a -> b) -> a -> b
$ do
Ptr PopupLayout
layout' <- PopupLayout -> IO (Ptr PopupLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PopupLayout
layout
Ptr PopupLayout
result <- Ptr PopupLayout -> IO (Ptr PopupLayout)
gdk_popup_layout_ref Ptr PopupLayout
layout'
Text -> Ptr PopupLayout -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"popupLayoutRef" Ptr PopupLayout
result
PopupLayout
result' <- ((ManagedPtr PopupLayout -> PopupLayout)
-> Ptr PopupLayout -> IO PopupLayout
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr PopupLayout -> PopupLayout
PopupLayout) Ptr PopupLayout
result
PopupLayout -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PopupLayout
layout
PopupLayout -> IO PopupLayout
forall (m :: * -> *) a. Monad m => a -> m a
return PopupLayout
result'
#if defined(ENABLE_OVERLOADING)
data PopupLayoutRefMethodInfo
instance (signature ~ (m PopupLayout), MonadIO m) => O.MethodInfo PopupLayoutRefMethodInfo PopupLayout signature where
overloadedMethod = popupLayoutRef
#endif
foreign import ccall "gdk_popup_layout_set_anchor_hints" ::
Ptr PopupLayout ->
CUInt ->
IO ()
popupLayoutSetAnchorHints ::
(B.CallStack.HasCallStack, MonadIO m) =>
PopupLayout
-> [Gdk.Flags.AnchorHints]
-> m ()
PopupLayout
layout [AnchorHints]
anchorHints = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr PopupLayout
layout' <- PopupLayout -> IO (Ptr PopupLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PopupLayout
layout
let anchorHints' :: CUInt
anchorHints' = [AnchorHints] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [AnchorHints]
anchorHints
Ptr PopupLayout -> CUInt -> IO ()
gdk_popup_layout_set_anchor_hints Ptr PopupLayout
layout' CUInt
anchorHints'
PopupLayout -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PopupLayout
layout
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PopupLayoutSetAnchorHintsMethodInfo
instance (signature ~ ([Gdk.Flags.AnchorHints] -> m ()), MonadIO m) => O.MethodInfo PopupLayoutSetAnchorHintsMethodInfo PopupLayout signature where
overloadedMethod = popupLayoutSetAnchorHints
#endif
foreign import ccall "gdk_popup_layout_set_anchor_rect" ::
Ptr PopupLayout ->
Ptr Gdk.Rectangle.Rectangle ->
IO ()
popupLayoutSetAnchorRect ::
(B.CallStack.HasCallStack, MonadIO m) =>
PopupLayout
-> Gdk.Rectangle.Rectangle
-> m ()
PopupLayout
layout Rectangle
anchorRect = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr PopupLayout
layout' <- PopupLayout -> IO (Ptr PopupLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PopupLayout
layout
Ptr Rectangle
anchorRect' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
anchorRect
Ptr PopupLayout -> Ptr Rectangle -> IO ()
gdk_popup_layout_set_anchor_rect Ptr PopupLayout
layout' Ptr Rectangle
anchorRect'
PopupLayout -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PopupLayout
layout
Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
anchorRect
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PopupLayoutSetAnchorRectMethodInfo
instance (signature ~ (Gdk.Rectangle.Rectangle -> m ()), MonadIO m) => O.MethodInfo PopupLayoutSetAnchorRectMethodInfo PopupLayout signature where
overloadedMethod = popupLayoutSetAnchorRect
#endif
foreign import ccall "gdk_popup_layout_set_offset" ::
Ptr PopupLayout ->
Int32 ->
Int32 ->
IO ()
popupLayoutSetOffset ::
(B.CallStack.HasCallStack, MonadIO m) =>
PopupLayout
-> Int32
-> Int32
-> m ()
PopupLayout
layout Int32
dx Int32
dy = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr PopupLayout
layout' <- PopupLayout -> IO (Ptr PopupLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PopupLayout
layout
Ptr PopupLayout -> Int32 -> Int32 -> IO ()
gdk_popup_layout_set_offset Ptr PopupLayout
layout' Int32
dx Int32
dy
PopupLayout -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PopupLayout
layout
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PopupLayoutSetOffsetMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ()), MonadIO m) => O.MethodInfo PopupLayoutSetOffsetMethodInfo PopupLayout signature where
overloadedMethod = popupLayoutSetOffset
#endif
foreign import ccall "gdk_popup_layout_set_rect_anchor" ::
Ptr PopupLayout ->
CUInt ->
IO ()
popupLayoutSetRectAnchor ::
(B.CallStack.HasCallStack, MonadIO m) =>
PopupLayout
-> Gdk.Enums.Gravity
-> m ()
PopupLayout
layout Gravity
anchor = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr PopupLayout
layout' <- PopupLayout -> IO (Ptr PopupLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PopupLayout
layout
let anchor' :: CUInt
anchor' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Gravity -> Int) -> Gravity -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Gravity -> Int
forall a. Enum a => a -> Int
fromEnum) Gravity
anchor
Ptr PopupLayout -> CUInt -> IO ()
gdk_popup_layout_set_rect_anchor Ptr PopupLayout
layout' CUInt
anchor'
PopupLayout -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PopupLayout
layout
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PopupLayoutSetRectAnchorMethodInfo
instance (signature ~ (Gdk.Enums.Gravity -> m ()), MonadIO m) => O.MethodInfo PopupLayoutSetRectAnchorMethodInfo PopupLayout signature where
overloadedMethod = popupLayoutSetRectAnchor
#endif
foreign import ccall "gdk_popup_layout_set_surface_anchor" ::
Ptr PopupLayout ->
CUInt ->
IO ()
popupLayoutSetSurfaceAnchor ::
(B.CallStack.HasCallStack, MonadIO m) =>
PopupLayout
-> Gdk.Enums.Gravity
-> m ()
PopupLayout
layout Gravity
anchor = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr PopupLayout
layout' <- PopupLayout -> IO (Ptr PopupLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PopupLayout
layout
let anchor' :: CUInt
anchor' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Gravity -> Int) -> Gravity -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Gravity -> Int
forall a. Enum a => a -> Int
fromEnum) Gravity
anchor
Ptr PopupLayout -> CUInt -> IO ()
gdk_popup_layout_set_surface_anchor Ptr PopupLayout
layout' CUInt
anchor'
PopupLayout -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PopupLayout
layout
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PopupLayoutSetSurfaceAnchorMethodInfo
instance (signature ~ (Gdk.Enums.Gravity -> m ()), MonadIO m) => O.MethodInfo PopupLayoutSetSurfaceAnchorMethodInfo PopupLayout signature where
overloadedMethod = popupLayoutSetSurfaceAnchor
#endif
foreign import ccall "gdk_popup_layout_unref" ::
Ptr PopupLayout ->
IO ()
popupLayoutUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
PopupLayout
-> m ()
PopupLayout
layout = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr PopupLayout
layout' <- PopupLayout -> IO (Ptr PopupLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PopupLayout
layout
Ptr PopupLayout -> IO ()
gdk_popup_layout_unref Ptr PopupLayout
layout'
PopupLayout -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PopupLayout
layout
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PopupLayoutUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo PopupLayoutUnrefMethodInfo PopupLayout signature where
overloadedMethod = popupLayoutUnref
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolvePopupLayoutMethod (t :: Symbol) (o :: *) :: * where
ResolvePopupLayoutMethod "copy" o = PopupLayoutCopyMethodInfo
ResolvePopupLayoutMethod "equal" o = PopupLayoutEqualMethodInfo
ResolvePopupLayoutMethod "ref" o = PopupLayoutRefMethodInfo
ResolvePopupLayoutMethod "unref" o = PopupLayoutUnrefMethodInfo
ResolvePopupLayoutMethod "getAnchorHints" o = PopupLayoutGetAnchorHintsMethodInfo
ResolvePopupLayoutMethod "getAnchorRect" o = PopupLayoutGetAnchorRectMethodInfo
ResolvePopupLayoutMethod "getOffset" o = PopupLayoutGetOffsetMethodInfo
ResolvePopupLayoutMethod "getRectAnchor" o = PopupLayoutGetRectAnchorMethodInfo
ResolvePopupLayoutMethod "getSurfaceAnchor" o = PopupLayoutGetSurfaceAnchorMethodInfo
ResolvePopupLayoutMethod "setAnchorHints" o = PopupLayoutSetAnchorHintsMethodInfo
ResolvePopupLayoutMethod "setAnchorRect" o = PopupLayoutSetAnchorRectMethodInfo
ResolvePopupLayoutMethod "setOffset" o = PopupLayoutSetOffsetMethodInfo
ResolvePopupLayoutMethod "setRectAnchor" o = PopupLayoutSetRectAnchorMethodInfo
ResolvePopupLayoutMethod "setSurfaceAnchor" o = PopupLayoutSetSurfaceAnchorMethodInfo
ResolvePopupLayoutMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolvePopupLayoutMethod t PopupLayout, O.MethodInfo info PopupLayout p) => OL.IsLabel t (PopupLayout -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif