{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Wnck.Structs.WorkspaceLayout
    ( 
    WorkspaceLayout(..)                     ,
    newZeroWorkspaceLayout                  ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveWorkspaceLayoutMethod            ,
#endif
 
    getWorkspaceLayoutCols                  ,
    setWorkspaceLayoutCols                  ,
#if defined(ENABLE_OVERLOADING)
    workspaceLayout_cols                    ,
#endif
    getWorkspaceLayoutCurrentCol            ,
    setWorkspaceLayoutCurrentCol            ,
#if defined(ENABLE_OVERLOADING)
    workspaceLayout_currentCol              ,
#endif
    getWorkspaceLayoutCurrentRow            ,
    setWorkspaceLayoutCurrentRow            ,
#if defined(ENABLE_OVERLOADING)
    workspaceLayout_currentRow              ,
#endif
    getWorkspaceLayoutGrid                  ,
    setWorkspaceLayoutGrid                  ,
#if defined(ENABLE_OVERLOADING)
    workspaceLayout_grid                    ,
#endif
    getWorkspaceLayoutGridArea              ,
    setWorkspaceLayoutGridArea              ,
#if defined(ENABLE_OVERLOADING)
    workspaceLayout_gridArea                ,
#endif
    getWorkspaceLayoutRows                  ,
    setWorkspaceLayoutRows                  ,
#if defined(ENABLE_OVERLOADING)
    workspaceLayout_rows                    ,
#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.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
newtype WorkspaceLayout = WorkspaceLayout (SP.ManagedPtr WorkspaceLayout)
    deriving (WorkspaceLayout -> WorkspaceLayout -> Bool
(WorkspaceLayout -> WorkspaceLayout -> Bool)
-> (WorkspaceLayout -> WorkspaceLayout -> Bool)
-> Eq WorkspaceLayout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WorkspaceLayout -> WorkspaceLayout -> Bool
== :: WorkspaceLayout -> WorkspaceLayout -> Bool
$c/= :: WorkspaceLayout -> WorkspaceLayout -> Bool
/= :: WorkspaceLayout -> WorkspaceLayout -> Bool
Eq)
instance SP.ManagedPtrNewtype WorkspaceLayout where
    toManagedPtr :: WorkspaceLayout -> ManagedPtr WorkspaceLayout
toManagedPtr (WorkspaceLayout ManagedPtr WorkspaceLayout
p) = ManagedPtr WorkspaceLayout
p
instance BoxedPtr WorkspaceLayout where
    boxedPtrCopy :: WorkspaceLayout -> IO WorkspaceLayout
boxedPtrCopy = \WorkspaceLayout
p -> WorkspaceLayout
-> (Ptr WorkspaceLayout -> IO WorkspaceLayout)
-> IO WorkspaceLayout
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr WorkspaceLayout
p (Int -> Ptr WorkspaceLayout -> IO (Ptr WorkspaceLayout)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
32 (Ptr WorkspaceLayout -> IO (Ptr WorkspaceLayout))
-> (Ptr WorkspaceLayout -> IO WorkspaceLayout)
-> Ptr WorkspaceLayout
-> IO WorkspaceLayout
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr WorkspaceLayout -> WorkspaceLayout)
-> Ptr WorkspaceLayout -> IO WorkspaceLayout
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr WorkspaceLayout -> WorkspaceLayout
WorkspaceLayout)
    boxedPtrFree :: WorkspaceLayout -> IO ()
boxedPtrFree = \WorkspaceLayout
x -> WorkspaceLayout -> (Ptr WorkspaceLayout -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr WorkspaceLayout
x Ptr WorkspaceLayout -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr WorkspaceLayout where
    boxedPtrCalloc :: IO (Ptr WorkspaceLayout)
boxedPtrCalloc = Int -> IO (Ptr WorkspaceLayout)
forall a. Int -> IO (Ptr a)
callocBytes Int
32
newZeroWorkspaceLayout :: MonadIO m => m WorkspaceLayout
newZeroWorkspaceLayout :: forall (m :: * -> *). MonadIO m => m WorkspaceLayout
newZeroWorkspaceLayout = IO WorkspaceLayout -> m WorkspaceLayout
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WorkspaceLayout -> m WorkspaceLayout)
-> IO WorkspaceLayout -> m WorkspaceLayout
forall a b. (a -> b) -> a -> b
$ IO (Ptr WorkspaceLayout)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr WorkspaceLayout)
-> (Ptr WorkspaceLayout -> IO WorkspaceLayout)
-> IO WorkspaceLayout
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr WorkspaceLayout -> WorkspaceLayout)
-> Ptr WorkspaceLayout -> IO WorkspaceLayout
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr WorkspaceLayout -> WorkspaceLayout
WorkspaceLayout
instance tag ~ 'AttrSet => Constructible WorkspaceLayout tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr WorkspaceLayout -> WorkspaceLayout)
-> [AttrOp WorkspaceLayout tag] -> m WorkspaceLayout
new ManagedPtr WorkspaceLayout -> WorkspaceLayout
_ [AttrOp WorkspaceLayout tag]
attrs = do
        WorkspaceLayout
o <- m WorkspaceLayout
forall (m :: * -> *). MonadIO m => m WorkspaceLayout
newZeroWorkspaceLayout
        WorkspaceLayout -> [AttrOp WorkspaceLayout 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set WorkspaceLayout
o [AttrOp WorkspaceLayout tag]
[AttrOp WorkspaceLayout 'AttrSet]
attrs
        WorkspaceLayout -> m WorkspaceLayout
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return WorkspaceLayout
o
getWorkspaceLayoutRows :: MonadIO m => WorkspaceLayout -> m Int32
getWorkspaceLayoutRows :: forall (m :: * -> *). MonadIO m => WorkspaceLayout -> m Int32
getWorkspaceLayoutRows WorkspaceLayout
s = 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
$ WorkspaceLayout -> (Ptr WorkspaceLayout -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WorkspaceLayout
s ((Ptr WorkspaceLayout -> IO Int32) -> IO Int32)
-> (Ptr WorkspaceLayout -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr WorkspaceLayout
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr WorkspaceLayout
ptr Ptr WorkspaceLayout -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO Int32
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setWorkspaceLayoutRows :: MonadIO m => WorkspaceLayout -> Int32 -> m ()
setWorkspaceLayoutRows :: forall (m :: * -> *). MonadIO m => WorkspaceLayout -> Int32 -> m ()
setWorkspaceLayoutRows WorkspaceLayout
s Int32
val = 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
$ WorkspaceLayout -> (Ptr WorkspaceLayout -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WorkspaceLayout
s ((Ptr WorkspaceLayout -> IO ()) -> IO ())
-> (Ptr WorkspaceLayout -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WorkspaceLayout
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WorkspaceLayout
ptr Ptr WorkspaceLayout -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data WorkspaceLayoutRowsFieldInfo
instance AttrInfo WorkspaceLayoutRowsFieldInfo where
    type AttrBaseTypeConstraint WorkspaceLayoutRowsFieldInfo = (~) WorkspaceLayout
    type AttrAllowedOps WorkspaceLayoutRowsFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint WorkspaceLayoutRowsFieldInfo = (~) Int32
    type AttrTransferTypeConstraint WorkspaceLayoutRowsFieldInfo = (~)Int32
    type AttrTransferType WorkspaceLayoutRowsFieldInfo = Int32
    type AttrGetType WorkspaceLayoutRowsFieldInfo = Int32
    type AttrLabel WorkspaceLayoutRowsFieldInfo = "rows"
    type AttrOrigin WorkspaceLayoutRowsFieldInfo = WorkspaceLayout
    attrGet = getWorkspaceLayoutRows
    attrSet = setWorkspaceLayoutRows
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Wnck.Structs.WorkspaceLayout.rows"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-wnck-3.0.14/docs/GI-Wnck-Structs-WorkspaceLayout.html#g:attr:rows"
        })
workspaceLayout_rows :: AttrLabelProxy "rows"
workspaceLayout_rows = AttrLabelProxy
#endif
getWorkspaceLayoutCols :: MonadIO m => WorkspaceLayout -> m Int32
getWorkspaceLayoutCols :: forall (m :: * -> *). MonadIO m => WorkspaceLayout -> m Int32
getWorkspaceLayoutCols WorkspaceLayout
s = 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
$ WorkspaceLayout -> (Ptr WorkspaceLayout -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WorkspaceLayout
s ((Ptr WorkspaceLayout -> IO Int32) -> IO Int32)
-> (Ptr WorkspaceLayout -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr WorkspaceLayout
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr WorkspaceLayout
ptr Ptr WorkspaceLayout -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) :: IO Int32
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setWorkspaceLayoutCols :: MonadIO m => WorkspaceLayout -> Int32 -> m ()
setWorkspaceLayoutCols :: forall (m :: * -> *). MonadIO m => WorkspaceLayout -> Int32 -> m ()
setWorkspaceLayoutCols WorkspaceLayout
s Int32
val = 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
$ WorkspaceLayout -> (Ptr WorkspaceLayout -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WorkspaceLayout
s ((Ptr WorkspaceLayout -> IO ()) -> IO ())
-> (Ptr WorkspaceLayout -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WorkspaceLayout
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WorkspaceLayout
ptr Ptr WorkspaceLayout -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data WorkspaceLayoutColsFieldInfo
instance AttrInfo WorkspaceLayoutColsFieldInfo where
    type AttrBaseTypeConstraint WorkspaceLayoutColsFieldInfo = (~) WorkspaceLayout
    type AttrAllowedOps WorkspaceLayoutColsFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint WorkspaceLayoutColsFieldInfo = (~) Int32
    type AttrTransferTypeConstraint WorkspaceLayoutColsFieldInfo = (~)Int32
    type AttrTransferType WorkspaceLayoutColsFieldInfo = Int32
    type AttrGetType WorkspaceLayoutColsFieldInfo = Int32
    type AttrLabel WorkspaceLayoutColsFieldInfo = "cols"
    type AttrOrigin WorkspaceLayoutColsFieldInfo = WorkspaceLayout
    attrGet = getWorkspaceLayoutCols
    attrSet = setWorkspaceLayoutCols
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Wnck.Structs.WorkspaceLayout.cols"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-wnck-3.0.14/docs/GI-Wnck-Structs-WorkspaceLayout.html#g:attr:cols"
        })
workspaceLayout_cols :: AttrLabelProxy "cols"
workspaceLayout_cols = AttrLabelProxy
#endif
getWorkspaceLayoutGrid :: MonadIO m => WorkspaceLayout -> m Int32
getWorkspaceLayoutGrid :: forall (m :: * -> *). MonadIO m => WorkspaceLayout -> m Int32
getWorkspaceLayoutGrid WorkspaceLayout
s = 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
$ WorkspaceLayout -> (Ptr WorkspaceLayout -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WorkspaceLayout
s ((Ptr WorkspaceLayout -> IO Int32) -> IO Int32)
-> (Ptr WorkspaceLayout -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr WorkspaceLayout
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr WorkspaceLayout
ptr Ptr WorkspaceLayout -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO Int32
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setWorkspaceLayoutGrid :: MonadIO m => WorkspaceLayout -> Int32 -> m ()
setWorkspaceLayoutGrid :: forall (m :: * -> *). MonadIO m => WorkspaceLayout -> Int32 -> m ()
setWorkspaceLayoutGrid WorkspaceLayout
s Int32
val = 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
$ WorkspaceLayout -> (Ptr WorkspaceLayout -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WorkspaceLayout
s ((Ptr WorkspaceLayout -> IO ()) -> IO ())
-> (Ptr WorkspaceLayout -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WorkspaceLayout
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WorkspaceLayout
ptr Ptr WorkspaceLayout -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data WorkspaceLayoutGridFieldInfo
instance AttrInfo WorkspaceLayoutGridFieldInfo where
    type AttrBaseTypeConstraint WorkspaceLayoutGridFieldInfo = (~) WorkspaceLayout
    type AttrAllowedOps WorkspaceLayoutGridFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint WorkspaceLayoutGridFieldInfo = (~) Int32
    type AttrTransferTypeConstraint WorkspaceLayoutGridFieldInfo = (~)Int32
    type AttrTransferType WorkspaceLayoutGridFieldInfo = Int32
    type AttrGetType WorkspaceLayoutGridFieldInfo = Int32
    type AttrLabel WorkspaceLayoutGridFieldInfo = "grid"
    type AttrOrigin WorkspaceLayoutGridFieldInfo = WorkspaceLayout
    attrGet = getWorkspaceLayoutGrid
    attrSet = setWorkspaceLayoutGrid
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Wnck.Structs.WorkspaceLayout.grid"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-wnck-3.0.14/docs/GI-Wnck-Structs-WorkspaceLayout.html#g:attr:grid"
        })
workspaceLayout_grid :: AttrLabelProxy "grid"
workspaceLayout_grid = AttrLabelProxy
#endif
getWorkspaceLayoutGridArea :: MonadIO m => WorkspaceLayout -> m Int32
getWorkspaceLayoutGridArea :: forall (m :: * -> *). MonadIO m => WorkspaceLayout -> m Int32
getWorkspaceLayoutGridArea WorkspaceLayout
s = 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
$ WorkspaceLayout -> (Ptr WorkspaceLayout -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WorkspaceLayout
s ((Ptr WorkspaceLayout -> IO Int32) -> IO Int32)
-> (Ptr WorkspaceLayout -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr WorkspaceLayout
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr WorkspaceLayout
ptr Ptr WorkspaceLayout -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO Int32
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setWorkspaceLayoutGridArea :: MonadIO m => WorkspaceLayout -> Int32 -> m ()
setWorkspaceLayoutGridArea :: forall (m :: * -> *). MonadIO m => WorkspaceLayout -> Int32 -> m ()
setWorkspaceLayoutGridArea WorkspaceLayout
s Int32
val = 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
$ WorkspaceLayout -> (Ptr WorkspaceLayout -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WorkspaceLayout
s ((Ptr WorkspaceLayout -> IO ()) -> IO ())
-> (Ptr WorkspaceLayout -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WorkspaceLayout
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WorkspaceLayout
ptr Ptr WorkspaceLayout -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data WorkspaceLayoutGridAreaFieldInfo
instance AttrInfo WorkspaceLayoutGridAreaFieldInfo where
    type AttrBaseTypeConstraint WorkspaceLayoutGridAreaFieldInfo = (~) WorkspaceLayout
    type AttrAllowedOps WorkspaceLayoutGridAreaFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint WorkspaceLayoutGridAreaFieldInfo = (~) Int32
    type AttrTransferTypeConstraint WorkspaceLayoutGridAreaFieldInfo = (~)Int32
    type AttrTransferType WorkspaceLayoutGridAreaFieldInfo = Int32
    type AttrGetType WorkspaceLayoutGridAreaFieldInfo = Int32
    type AttrLabel WorkspaceLayoutGridAreaFieldInfo = "grid_area"
    type AttrOrigin WorkspaceLayoutGridAreaFieldInfo = WorkspaceLayout
    attrGet = getWorkspaceLayoutGridArea
    attrSet = setWorkspaceLayoutGridArea
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Wnck.Structs.WorkspaceLayout.gridArea"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-wnck-3.0.14/docs/GI-Wnck-Structs-WorkspaceLayout.html#g:attr:gridArea"
        })
workspaceLayout_gridArea :: AttrLabelProxy "gridArea"
workspaceLayout_gridArea = AttrLabelProxy
#endif
getWorkspaceLayoutCurrentRow :: MonadIO m => WorkspaceLayout -> m Int32
getWorkspaceLayoutCurrentRow :: forall (m :: * -> *). MonadIO m => WorkspaceLayout -> m Int32
getWorkspaceLayoutCurrentRow WorkspaceLayout
s = 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
$ WorkspaceLayout -> (Ptr WorkspaceLayout -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WorkspaceLayout
s ((Ptr WorkspaceLayout -> IO Int32) -> IO Int32)
-> (Ptr WorkspaceLayout -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr WorkspaceLayout
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr WorkspaceLayout
ptr Ptr WorkspaceLayout -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20) :: IO Int32
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setWorkspaceLayoutCurrentRow :: MonadIO m => WorkspaceLayout -> Int32 -> m ()
setWorkspaceLayoutCurrentRow :: forall (m :: * -> *). MonadIO m => WorkspaceLayout -> Int32 -> m ()
setWorkspaceLayoutCurrentRow WorkspaceLayout
s Int32
val = 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
$ WorkspaceLayout -> (Ptr WorkspaceLayout -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WorkspaceLayout
s ((Ptr WorkspaceLayout -> IO ()) -> IO ())
-> (Ptr WorkspaceLayout -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WorkspaceLayout
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WorkspaceLayout
ptr Ptr WorkspaceLayout -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data WorkspaceLayoutCurrentRowFieldInfo
instance AttrInfo WorkspaceLayoutCurrentRowFieldInfo where
    type AttrBaseTypeConstraint WorkspaceLayoutCurrentRowFieldInfo = (~) WorkspaceLayout
    type AttrAllowedOps WorkspaceLayoutCurrentRowFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint WorkspaceLayoutCurrentRowFieldInfo = (~) Int32
    type AttrTransferTypeConstraint WorkspaceLayoutCurrentRowFieldInfo = (~)Int32
    type AttrTransferType WorkspaceLayoutCurrentRowFieldInfo = Int32
    type AttrGetType WorkspaceLayoutCurrentRowFieldInfo = Int32
    type AttrLabel WorkspaceLayoutCurrentRowFieldInfo = "current_row"
    type AttrOrigin WorkspaceLayoutCurrentRowFieldInfo = WorkspaceLayout
    attrGet = getWorkspaceLayoutCurrentRow
    attrSet = setWorkspaceLayoutCurrentRow
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Wnck.Structs.WorkspaceLayout.currentRow"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-wnck-3.0.14/docs/GI-Wnck-Structs-WorkspaceLayout.html#g:attr:currentRow"
        })
workspaceLayout_currentRow :: AttrLabelProxy "currentRow"
workspaceLayout_currentRow = AttrLabelProxy
#endif
getWorkspaceLayoutCurrentCol :: MonadIO m => WorkspaceLayout -> m Int32
getWorkspaceLayoutCurrentCol :: forall (m :: * -> *). MonadIO m => WorkspaceLayout -> m Int32
getWorkspaceLayoutCurrentCol WorkspaceLayout
s = 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
$ WorkspaceLayout -> (Ptr WorkspaceLayout -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WorkspaceLayout
s ((Ptr WorkspaceLayout -> IO Int32) -> IO Int32)
-> (Ptr WorkspaceLayout -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr WorkspaceLayout
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr WorkspaceLayout
ptr Ptr WorkspaceLayout -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO Int32
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setWorkspaceLayoutCurrentCol :: MonadIO m => WorkspaceLayout -> Int32 -> m ()
setWorkspaceLayoutCurrentCol :: forall (m :: * -> *). MonadIO m => WorkspaceLayout -> Int32 -> m ()
setWorkspaceLayoutCurrentCol WorkspaceLayout
s Int32
val = 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
$ WorkspaceLayout -> (Ptr WorkspaceLayout -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WorkspaceLayout
s ((Ptr WorkspaceLayout -> IO ()) -> IO ())
-> (Ptr WorkspaceLayout -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WorkspaceLayout
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WorkspaceLayout
ptr Ptr WorkspaceLayout -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data WorkspaceLayoutCurrentColFieldInfo
instance AttrInfo WorkspaceLayoutCurrentColFieldInfo where
    type AttrBaseTypeConstraint WorkspaceLayoutCurrentColFieldInfo = (~) WorkspaceLayout
    type AttrAllowedOps WorkspaceLayoutCurrentColFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint WorkspaceLayoutCurrentColFieldInfo = (~) Int32
    type AttrTransferTypeConstraint WorkspaceLayoutCurrentColFieldInfo = (~)Int32
    type AttrTransferType WorkspaceLayoutCurrentColFieldInfo = Int32
    type AttrGetType WorkspaceLayoutCurrentColFieldInfo = Int32
    type AttrLabel WorkspaceLayoutCurrentColFieldInfo = "current_col"
    type AttrOrigin WorkspaceLayoutCurrentColFieldInfo = WorkspaceLayout
    attrGet = getWorkspaceLayoutCurrentCol
    attrSet = setWorkspaceLayoutCurrentCol
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Wnck.Structs.WorkspaceLayout.currentCol"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-wnck-3.0.14/docs/GI-Wnck-Structs-WorkspaceLayout.html#g:attr:currentCol"
        })
workspaceLayout_currentCol :: AttrLabelProxy "currentCol"
workspaceLayout_currentCol = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList WorkspaceLayout
type instance O.AttributeList WorkspaceLayout = WorkspaceLayoutAttributeList
type WorkspaceLayoutAttributeList = ('[ '("rows", WorkspaceLayoutRowsFieldInfo), '("cols", WorkspaceLayoutColsFieldInfo), '("grid", WorkspaceLayoutGridFieldInfo), '("gridArea", WorkspaceLayoutGridAreaFieldInfo), '("currentRow", WorkspaceLayoutCurrentRowFieldInfo), '("currentCol", WorkspaceLayoutCurrentColFieldInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveWorkspaceLayoutMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveWorkspaceLayoutMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveWorkspaceLayoutMethod t WorkspaceLayout, O.OverloadedMethod info WorkspaceLayout p) => OL.IsLabel t (WorkspaceLayout -> 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 ~ ResolveWorkspaceLayoutMethod t WorkspaceLayout, O.OverloadedMethod info WorkspaceLayout p, R.HasField t WorkspaceLayout p) => R.HasField t WorkspaceLayout p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveWorkspaceLayoutMethod t WorkspaceLayout, O.OverloadedMethodInfo info WorkspaceLayout) => OL.IsLabel t (O.MethodProxy info WorkspaceLayout) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif