{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Structs.ToplevelLayout
(
ToplevelLayout(..) ,
#if defined(ENABLE_OVERLOADING)
ResolveToplevelLayoutMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ToplevelLayoutCopyMethodInfo ,
#endif
toplevelLayoutCopy ,
#if defined(ENABLE_OVERLOADING)
ToplevelLayoutEqualMethodInfo ,
#endif
toplevelLayoutEqual ,
#if defined(ENABLE_OVERLOADING)
ToplevelLayoutGetFullscreenMethodInfo ,
#endif
toplevelLayoutGetFullscreen ,
#if defined(ENABLE_OVERLOADING)
ToplevelLayoutGetFullscreenMonitorMethodInfo,
#endif
toplevelLayoutGetFullscreenMonitor ,
#if defined(ENABLE_OVERLOADING)
ToplevelLayoutGetMaximizedMethodInfo ,
#endif
toplevelLayoutGetMaximized ,
#if defined(ENABLE_OVERLOADING)
ToplevelLayoutGetResizableMethodInfo ,
#endif
toplevelLayoutGetResizable ,
toplevelLayoutNew ,
#if defined(ENABLE_OVERLOADING)
ToplevelLayoutRefMethodInfo ,
#endif
toplevelLayoutRef ,
#if defined(ENABLE_OVERLOADING)
ToplevelLayoutSetFullscreenMethodInfo ,
#endif
toplevelLayoutSetFullscreen ,
#if defined(ENABLE_OVERLOADING)
ToplevelLayoutSetMaximizedMethodInfo ,
#endif
toplevelLayoutSetMaximized ,
#if defined(ENABLE_OVERLOADING)
ToplevelLayoutSetResizableMethodInfo ,
#endif
toplevelLayoutSetResizable ,
#if defined(ENABLE_OVERLOADING)
ToplevelLayoutUnrefMethodInfo ,
#endif
toplevelLayoutUnref ,
) 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.Kind as DK
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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.Cairo.Enums as Cairo.Enums
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.Region as Cairo.Region
import qualified GI.Cairo.Structs.Surface as Cairo.Surface
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.String as GLib.String
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Interfaces.Paintable as Gdk.Paintable
import {-# SOURCE #-} qualified GI.Gdk.Objects.AppLaunchContext as Gdk.AppLaunchContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.CairoContext as Gdk.CairoContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Clipboard as Gdk.Clipboard
import {-# SOURCE #-} qualified GI.Gdk.Objects.ContentProvider as Gdk.ContentProvider
import {-# SOURCE #-} qualified GI.Gdk.Objects.Cursor as Gdk.Cursor
import {-# SOURCE #-} qualified GI.Gdk.Objects.Device as Gdk.Device
import {-# SOURCE #-} qualified GI.Gdk.Objects.DeviceTool as Gdk.DeviceTool
import {-# SOURCE #-} qualified GI.Gdk.Objects.Display as Gdk.Display
import {-# SOURCE #-} qualified GI.Gdk.Objects.DrawContext as Gdk.DrawContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Event as Gdk.Event
import {-# SOURCE #-} qualified GI.Gdk.Objects.FrameClock as Gdk.FrameClock
import {-# SOURCE #-} qualified GI.Gdk.Objects.GLContext as Gdk.GLContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Monitor as Gdk.Monitor
import {-# SOURCE #-} qualified GI.Gdk.Objects.Seat as Gdk.Seat
import {-# SOURCE #-} qualified GI.Gdk.Objects.Snapshot as Gdk.Snapshot
import {-# SOURCE #-} qualified GI.Gdk.Objects.Surface as Gdk.Surface
import {-# SOURCE #-} qualified GI.Gdk.Objects.Texture as Gdk.Texture
import {-# SOURCE #-} qualified GI.Gdk.Objects.VulkanContext as Gdk.VulkanContext
import {-# SOURCE #-} qualified GI.Gdk.Structs.ContentFormats as Gdk.ContentFormats
import {-# SOURCE #-} qualified GI.Gdk.Structs.DmabufFormats as Gdk.DmabufFormats
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSequence as Gdk.EventSequence
import {-# SOURCE #-} qualified GI.Gdk.Structs.FrameTimings as Gdk.FrameTimings
import {-# SOURCE #-} qualified GI.Gdk.Structs.KeymapKey as Gdk.KeymapKey
import {-# SOURCE #-} qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import {-# SOURCE #-} qualified GI.Gdk.Structs.TimeCoord as Gdk.TimeCoord
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Interfaces.File as Gio.File
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Interfaces.Initable as Gio.Initable
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import qualified GI.Gio.Interfaces.LoadableIcon as Gio.LoadableIcon
import qualified GI.Gio.Objects.AppLaunchContext as Gio.AppLaunchContext
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.Gio.Objects.InputStream as Gio.InputStream
import qualified GI.Gio.Objects.OutputStream as Gio.OutputStream
import qualified GI.Pango.Enums as Pango.Enums
#else
import {-# SOURCE #-} qualified GI.Gdk.Objects.Monitor as Gdk.Monitor
#endif
newtype ToplevelLayout = ToplevelLayout (SP.ManagedPtr ToplevelLayout)
deriving (ToplevelLayout -> ToplevelLayout -> Bool
(ToplevelLayout -> ToplevelLayout -> Bool)
-> (ToplevelLayout -> ToplevelLayout -> Bool) -> Eq ToplevelLayout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ToplevelLayout -> ToplevelLayout -> Bool
== :: ToplevelLayout -> ToplevelLayout -> Bool
$c/= :: ToplevelLayout -> ToplevelLayout -> Bool
/= :: ToplevelLayout -> ToplevelLayout -> Bool
Eq)
instance SP.ManagedPtrNewtype ToplevelLayout where
toManagedPtr :: ToplevelLayout -> ManagedPtr ToplevelLayout
toManagedPtr (ToplevelLayout ManagedPtr ToplevelLayout
p) = ManagedPtr ToplevelLayout
p
foreign import ccall "gdk_toplevel_layout_get_type" c_gdk_toplevel_layout_get_type ::
IO GType
type instance O.ParentTypes ToplevelLayout = '[]
instance O.HasParentTypes ToplevelLayout
instance B.Types.TypedObject ToplevelLayout where
glibType :: IO GType
glibType = IO GType
c_gdk_toplevel_layout_get_type
instance B.Types.GBoxed ToplevelLayout
instance B.GValue.IsGValue (Maybe ToplevelLayout) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_toplevel_layout_get_type
gvalueSet_ :: Ptr GValue -> Maybe ToplevelLayout -> IO ()
gvalueSet_ Ptr GValue
gv Maybe ToplevelLayout
P.Nothing = Ptr GValue -> Ptr ToplevelLayout -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr ToplevelLayout
forall a. Ptr a
FP.nullPtr :: FP.Ptr ToplevelLayout)
gvalueSet_ Ptr GValue
gv (P.Just ToplevelLayout
obj) = ToplevelLayout -> (Ptr ToplevelLayout -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ToplevelLayout
obj (Ptr GValue -> Ptr ToplevelLayout -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe ToplevelLayout)
gvalueGet_ Ptr GValue
gv = do
ptr <- Ptr GValue -> IO (Ptr ToplevelLayout)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr ToplevelLayout)
if ptr /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newBoxed ToplevelLayout ptr
else return P.Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ToplevelLayout
type instance O.AttributeList ToplevelLayout = ToplevelLayoutAttributeList
type ToplevelLayoutAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gdk_toplevel_layout_new" gdk_toplevel_layout_new ::
IO (Ptr ToplevelLayout)
toplevelLayoutNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m ToplevelLayout
toplevelLayoutNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m ToplevelLayout
toplevelLayoutNew = IO ToplevelLayout -> m ToplevelLayout
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ToplevelLayout -> m ToplevelLayout)
-> IO ToplevelLayout -> m ToplevelLayout
forall a b. (a -> b) -> a -> b
$ do
result <- IO (Ptr ToplevelLayout)
gdk_toplevel_layout_new
checkUnexpectedReturnNULL "toplevelLayoutNew" result
result' <- (wrapBoxed ToplevelLayout) result
return result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gdk_toplevel_layout_copy" gdk_toplevel_layout_copy ::
Ptr ToplevelLayout ->
IO (Ptr ToplevelLayout)
toplevelLayoutCopy ::
(B.CallStack.HasCallStack, MonadIO m) =>
ToplevelLayout
-> m ToplevelLayout
toplevelLayoutCopy :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ToplevelLayout -> m ToplevelLayout
toplevelLayoutCopy ToplevelLayout
layout = IO ToplevelLayout -> m ToplevelLayout
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ToplevelLayout -> m ToplevelLayout)
-> IO ToplevelLayout -> m ToplevelLayout
forall a b. (a -> b) -> a -> b
$ do
layout' <- ToplevelLayout -> IO (Ptr ToplevelLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ToplevelLayout
layout
result <- gdk_toplevel_layout_copy layout'
checkUnexpectedReturnNULL "toplevelLayoutCopy" result
result' <- (wrapBoxed ToplevelLayout) result
touchManagedPtr layout
return result'
#if defined(ENABLE_OVERLOADING)
data ToplevelLayoutCopyMethodInfo
instance (signature ~ (m ToplevelLayout), MonadIO m) => O.OverloadedMethod ToplevelLayoutCopyMethodInfo ToplevelLayout signature where
overloadedMethod = toplevelLayoutCopy
instance O.OverloadedMethodInfo ToplevelLayoutCopyMethodInfo ToplevelLayout where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.ToplevelLayout.toplevelLayoutCopy",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Structs-ToplevelLayout.html#v:toplevelLayoutCopy"
})
#endif
foreign import ccall "gdk_toplevel_layout_equal" gdk_toplevel_layout_equal ::
Ptr ToplevelLayout ->
Ptr ToplevelLayout ->
IO CInt
toplevelLayoutEqual ::
(B.CallStack.HasCallStack, MonadIO m) =>
ToplevelLayout
-> ToplevelLayout
-> m Bool
toplevelLayoutEqual :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ToplevelLayout -> ToplevelLayout -> m Bool
toplevelLayoutEqual ToplevelLayout
layout ToplevelLayout
other = 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
layout' <- ToplevelLayout -> IO (Ptr ToplevelLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ToplevelLayout
layout
other' <- unsafeManagedPtrGetPtr other
result <- gdk_toplevel_layout_equal layout' other'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr layout
touchManagedPtr other
return result'
#if defined(ENABLE_OVERLOADING)
data ToplevelLayoutEqualMethodInfo
instance (signature ~ (ToplevelLayout -> m Bool), MonadIO m) => O.OverloadedMethod ToplevelLayoutEqualMethodInfo ToplevelLayout signature where
overloadedMethod = toplevelLayoutEqual
instance O.OverloadedMethodInfo ToplevelLayoutEqualMethodInfo ToplevelLayout where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.ToplevelLayout.toplevelLayoutEqual",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Structs-ToplevelLayout.html#v:toplevelLayoutEqual"
})
#endif
foreign import ccall "gdk_toplevel_layout_get_fullscreen" gdk_toplevel_layout_get_fullscreen ::
Ptr ToplevelLayout ->
Ptr CInt ->
IO CInt
toplevelLayoutGetFullscreen ::
(B.CallStack.HasCallStack, MonadIO m) =>
ToplevelLayout
-> m ((Bool, Bool))
toplevelLayoutGetFullscreen :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ToplevelLayout -> m (Bool, Bool)
toplevelLayoutGetFullscreen ToplevelLayout
layout = IO (Bool, Bool) -> m (Bool, Bool)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Bool) -> m (Bool, Bool))
-> IO (Bool, Bool) -> m (Bool, Bool)
forall a b. (a -> b) -> a -> b
$ do
layout' <- ToplevelLayout -> IO (Ptr ToplevelLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ToplevelLayout
layout
fullscreen <- allocMem :: IO (Ptr CInt)
result <- gdk_toplevel_layout_get_fullscreen layout' fullscreen
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
fullscreen' <- peek fullscreen
let fullscreen'' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
fullscreen'
touchManagedPtr layout
freeMem fullscreen
return (result', fullscreen'')
#if defined(ENABLE_OVERLOADING)
data ToplevelLayoutGetFullscreenMethodInfo
instance (signature ~ (m ((Bool, Bool))), MonadIO m) => O.OverloadedMethod ToplevelLayoutGetFullscreenMethodInfo ToplevelLayout signature where
overloadedMethod = toplevelLayoutGetFullscreen
instance O.OverloadedMethodInfo ToplevelLayoutGetFullscreenMethodInfo ToplevelLayout where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.ToplevelLayout.toplevelLayoutGetFullscreen",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Structs-ToplevelLayout.html#v:toplevelLayoutGetFullscreen"
})
#endif
foreign import ccall "gdk_toplevel_layout_get_fullscreen_monitor" gdk_toplevel_layout_get_fullscreen_monitor ::
Ptr ToplevelLayout ->
IO (Ptr Gdk.Monitor.Monitor)
toplevelLayoutGetFullscreenMonitor ::
(B.CallStack.HasCallStack, MonadIO m) =>
ToplevelLayout
-> m (Maybe Gdk.Monitor.Monitor)
toplevelLayoutGetFullscreenMonitor :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ToplevelLayout -> m (Maybe Monitor)
toplevelLayoutGetFullscreenMonitor ToplevelLayout
layout = IO (Maybe Monitor) -> m (Maybe Monitor)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Monitor) -> m (Maybe Monitor))
-> IO (Maybe Monitor) -> m (Maybe Monitor)
forall a b. (a -> b) -> a -> b
$ do
layout' <- ToplevelLayout -> IO (Ptr ToplevelLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ToplevelLayout
layout
result <- gdk_toplevel_layout_get_fullscreen_monitor layout'
maybeResult <- convertIfNonNull result $ \Ptr Monitor
result' -> do
result'' <- ((ManagedPtr Monitor -> Monitor) -> Ptr Monitor -> IO Monitor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Monitor -> Monitor
Gdk.Monitor.Monitor) Ptr Monitor
result'
return result''
touchManagedPtr layout
return maybeResult
#if defined(ENABLE_OVERLOADING)
data ToplevelLayoutGetFullscreenMonitorMethodInfo
instance (signature ~ (m (Maybe Gdk.Monitor.Monitor)), MonadIO m) => O.OverloadedMethod ToplevelLayoutGetFullscreenMonitorMethodInfo ToplevelLayout signature where
overloadedMethod = toplevelLayoutGetFullscreenMonitor
instance O.OverloadedMethodInfo ToplevelLayoutGetFullscreenMonitorMethodInfo ToplevelLayout where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.ToplevelLayout.toplevelLayoutGetFullscreenMonitor",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Structs-ToplevelLayout.html#v:toplevelLayoutGetFullscreenMonitor"
})
#endif
foreign import ccall "gdk_toplevel_layout_get_maximized" gdk_toplevel_layout_get_maximized ::
Ptr ToplevelLayout ->
Ptr CInt ->
IO CInt
toplevelLayoutGetMaximized ::
(B.CallStack.HasCallStack, MonadIO m) =>
ToplevelLayout
-> m ((Bool, Bool))
toplevelLayoutGetMaximized :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ToplevelLayout -> m (Bool, Bool)
toplevelLayoutGetMaximized ToplevelLayout
layout = IO (Bool, Bool) -> m (Bool, Bool)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Bool) -> m (Bool, Bool))
-> IO (Bool, Bool) -> m (Bool, Bool)
forall a b. (a -> b) -> a -> b
$ do
layout' <- ToplevelLayout -> IO (Ptr ToplevelLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ToplevelLayout
layout
maximized <- allocMem :: IO (Ptr CInt)
result <- gdk_toplevel_layout_get_maximized layout' maximized
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
maximized' <- peek maximized
let maximized'' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
maximized'
touchManagedPtr layout
freeMem maximized
return (result', maximized'')
#if defined(ENABLE_OVERLOADING)
data ToplevelLayoutGetMaximizedMethodInfo
instance (signature ~ (m ((Bool, Bool))), MonadIO m) => O.OverloadedMethod ToplevelLayoutGetMaximizedMethodInfo ToplevelLayout signature where
overloadedMethod = toplevelLayoutGetMaximized
instance O.OverloadedMethodInfo ToplevelLayoutGetMaximizedMethodInfo ToplevelLayout where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.ToplevelLayout.toplevelLayoutGetMaximized",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Structs-ToplevelLayout.html#v:toplevelLayoutGetMaximized"
})
#endif
foreign import ccall "gdk_toplevel_layout_get_resizable" gdk_toplevel_layout_get_resizable ::
Ptr ToplevelLayout ->
IO CInt
toplevelLayoutGetResizable ::
(B.CallStack.HasCallStack, MonadIO m) =>
ToplevelLayout
-> m Bool
toplevelLayoutGetResizable :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ToplevelLayout -> m Bool
toplevelLayoutGetResizable ToplevelLayout
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
layout' <- ToplevelLayout -> IO (Ptr ToplevelLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ToplevelLayout
layout
result <- gdk_toplevel_layout_get_resizable layout'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr layout
return result'
#if defined(ENABLE_OVERLOADING)
data ToplevelLayoutGetResizableMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod ToplevelLayoutGetResizableMethodInfo ToplevelLayout signature where
overloadedMethod = toplevelLayoutGetResizable
instance O.OverloadedMethodInfo ToplevelLayoutGetResizableMethodInfo ToplevelLayout where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.ToplevelLayout.toplevelLayoutGetResizable",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Structs-ToplevelLayout.html#v:toplevelLayoutGetResizable"
})
#endif
foreign import ccall "gdk_toplevel_layout_ref" gdk_toplevel_layout_ref ::
Ptr ToplevelLayout ->
IO (Ptr ToplevelLayout)
toplevelLayoutRef ::
(B.CallStack.HasCallStack, MonadIO m) =>
ToplevelLayout
-> m ToplevelLayout
toplevelLayoutRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ToplevelLayout -> m ToplevelLayout
toplevelLayoutRef ToplevelLayout
layout = IO ToplevelLayout -> m ToplevelLayout
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ToplevelLayout -> m ToplevelLayout)
-> IO ToplevelLayout -> m ToplevelLayout
forall a b. (a -> b) -> a -> b
$ do
layout' <- ToplevelLayout -> IO (Ptr ToplevelLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ToplevelLayout
layout
result <- gdk_toplevel_layout_ref layout'
checkUnexpectedReturnNULL "toplevelLayoutRef" result
result' <- (wrapBoxed ToplevelLayout) result
touchManagedPtr layout
return result'
#if defined(ENABLE_OVERLOADING)
data ToplevelLayoutRefMethodInfo
instance (signature ~ (m ToplevelLayout), MonadIO m) => O.OverloadedMethod ToplevelLayoutRefMethodInfo ToplevelLayout signature where
overloadedMethod = toplevelLayoutRef
instance O.OverloadedMethodInfo ToplevelLayoutRefMethodInfo ToplevelLayout where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.ToplevelLayout.toplevelLayoutRef",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Structs-ToplevelLayout.html#v:toplevelLayoutRef"
})
#endif
foreign import ccall "gdk_toplevel_layout_set_fullscreen" gdk_toplevel_layout_set_fullscreen ::
Ptr ToplevelLayout ->
CInt ->
Ptr Gdk.Monitor.Monitor ->
IO ()
toplevelLayoutSetFullscreen ::
(B.CallStack.HasCallStack, MonadIO m, Gdk.Monitor.IsMonitor a) =>
ToplevelLayout
-> Bool
-> Maybe (a)
-> m ()
toplevelLayoutSetFullscreen :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMonitor a) =>
ToplevelLayout -> Bool -> Maybe a -> m ()
toplevelLayoutSetFullscreen ToplevelLayout
layout Bool
fullscreen Maybe a
monitor = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
layout' <- ToplevelLayout -> IO (Ptr ToplevelLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ToplevelLayout
layout
let fullscreen' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
fullscreen
maybeMonitor <- case monitor of
Maybe a
Nothing -> Ptr Monitor -> IO (Ptr Monitor)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Monitor
forall a. Ptr a
FP.nullPtr
Just a
jMonitor -> do
jMonitor' <- a -> IO (Ptr Monitor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jMonitor
return jMonitor'
gdk_toplevel_layout_set_fullscreen layout' fullscreen' maybeMonitor
touchManagedPtr layout
whenJust monitor touchManagedPtr
return ()
#if defined(ENABLE_OVERLOADING)
data ToplevelLayoutSetFullscreenMethodInfo
instance (signature ~ (Bool -> Maybe (a) -> m ()), MonadIO m, Gdk.Monitor.IsMonitor a) => O.OverloadedMethod ToplevelLayoutSetFullscreenMethodInfo ToplevelLayout signature where
overloadedMethod = toplevelLayoutSetFullscreen
instance O.OverloadedMethodInfo ToplevelLayoutSetFullscreenMethodInfo ToplevelLayout where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.ToplevelLayout.toplevelLayoutSetFullscreen",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Structs-ToplevelLayout.html#v:toplevelLayoutSetFullscreen"
})
#endif
foreign import ccall "gdk_toplevel_layout_set_maximized" gdk_toplevel_layout_set_maximized ::
Ptr ToplevelLayout ->
CInt ->
IO ()
toplevelLayoutSetMaximized ::
(B.CallStack.HasCallStack, MonadIO m) =>
ToplevelLayout
-> Bool
-> m ()
toplevelLayoutSetMaximized :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ToplevelLayout -> Bool -> m ()
toplevelLayoutSetMaximized ToplevelLayout
layout Bool
maximized = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
layout' <- ToplevelLayout -> IO (Ptr ToplevelLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ToplevelLayout
layout
let maximized' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
maximized
gdk_toplevel_layout_set_maximized layout' maximized'
touchManagedPtr layout
return ()
#if defined(ENABLE_OVERLOADING)
data ToplevelLayoutSetMaximizedMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m) => O.OverloadedMethod ToplevelLayoutSetMaximizedMethodInfo ToplevelLayout signature where
overloadedMethod = toplevelLayoutSetMaximized
instance O.OverloadedMethodInfo ToplevelLayoutSetMaximizedMethodInfo ToplevelLayout where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.ToplevelLayout.toplevelLayoutSetMaximized",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Structs-ToplevelLayout.html#v:toplevelLayoutSetMaximized"
})
#endif
foreign import ccall "gdk_toplevel_layout_set_resizable" gdk_toplevel_layout_set_resizable ::
Ptr ToplevelLayout ->
CInt ->
IO ()
toplevelLayoutSetResizable ::
(B.CallStack.HasCallStack, MonadIO m) =>
ToplevelLayout
-> Bool
-> m ()
toplevelLayoutSetResizable :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ToplevelLayout -> Bool -> m ()
toplevelLayoutSetResizable ToplevelLayout
layout Bool
resizable = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
layout' <- ToplevelLayout -> IO (Ptr ToplevelLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ToplevelLayout
layout
let resizable' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
resizable
gdk_toplevel_layout_set_resizable layout' resizable'
touchManagedPtr layout
return ()
#if defined(ENABLE_OVERLOADING)
data ToplevelLayoutSetResizableMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m) => O.OverloadedMethod ToplevelLayoutSetResizableMethodInfo ToplevelLayout signature where
overloadedMethod = toplevelLayoutSetResizable
instance O.OverloadedMethodInfo ToplevelLayoutSetResizableMethodInfo ToplevelLayout where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.ToplevelLayout.toplevelLayoutSetResizable",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Structs-ToplevelLayout.html#v:toplevelLayoutSetResizable"
})
#endif
foreign import ccall "gdk_toplevel_layout_unref" gdk_toplevel_layout_unref ::
Ptr ToplevelLayout ->
IO ()
toplevelLayoutUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
ToplevelLayout
-> m ()
toplevelLayoutUnref :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ToplevelLayout -> m ()
toplevelLayoutUnref ToplevelLayout
layout = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
layout' <- ToplevelLayout -> IO (Ptr ToplevelLayout)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ToplevelLayout
layout
gdk_toplevel_layout_unref layout'
touchManagedPtr layout
return ()
#if defined(ENABLE_OVERLOADING)
data ToplevelLayoutUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod ToplevelLayoutUnrefMethodInfo ToplevelLayout signature where
overloadedMethod = toplevelLayoutUnref
instance O.OverloadedMethodInfo ToplevelLayoutUnrefMethodInfo ToplevelLayout where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.ToplevelLayout.toplevelLayoutUnref",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Structs-ToplevelLayout.html#v:toplevelLayoutUnref"
})
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveToplevelLayoutMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveToplevelLayoutMethod "copy" o = ToplevelLayoutCopyMethodInfo
ResolveToplevelLayoutMethod "equal" o = ToplevelLayoutEqualMethodInfo
ResolveToplevelLayoutMethod "ref" o = ToplevelLayoutRefMethodInfo
ResolveToplevelLayoutMethod "unref" o = ToplevelLayoutUnrefMethodInfo
ResolveToplevelLayoutMethod "getFullscreen" o = ToplevelLayoutGetFullscreenMethodInfo
ResolveToplevelLayoutMethod "getFullscreenMonitor" o = ToplevelLayoutGetFullscreenMonitorMethodInfo
ResolveToplevelLayoutMethod "getMaximized" o = ToplevelLayoutGetMaximizedMethodInfo
ResolveToplevelLayoutMethod "getResizable" o = ToplevelLayoutGetResizableMethodInfo
ResolveToplevelLayoutMethod "setFullscreen" o = ToplevelLayoutSetFullscreenMethodInfo
ResolveToplevelLayoutMethod "setMaximized" o = ToplevelLayoutSetMaximizedMethodInfo
ResolveToplevelLayoutMethod "setResizable" o = ToplevelLayoutSetResizableMethodInfo
ResolveToplevelLayoutMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveToplevelLayoutMethod t ToplevelLayout, O.OverloadedMethod info ToplevelLayout p) => OL.IsLabel t (ToplevelLayout -> 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 ~ ResolveToplevelLayoutMethod t ToplevelLayout, O.OverloadedMethod info ToplevelLayout p, R.HasField t ToplevelLayout p) => R.HasField t ToplevelLayout p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveToplevelLayoutMethod t ToplevelLayout, O.OverloadedMethodInfo info ToplevelLayout) => OL.IsLabel t (O.MethodProxy info ToplevelLayout) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif