{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Structs.TableRowCol
(
TableRowCol(..) ,
newZeroTableRowCol ,
#if defined(ENABLE_OVERLOADING)
ResolveTableRowColMethod ,
#endif
getTableRowColAllocation ,
setTableRowColAllocation ,
#if defined(ENABLE_OVERLOADING)
tableRowCol_allocation ,
#endif
getTableRowColEmpty ,
setTableRowColEmpty ,
#if defined(ENABLE_OVERLOADING)
tableRowCol_empty ,
#endif
getTableRowColExpand ,
setTableRowColExpand ,
#if defined(ENABLE_OVERLOADING)
tableRowCol_expand ,
#endif
getTableRowColNeedExpand ,
setTableRowColNeedExpand ,
#if defined(ENABLE_OVERLOADING)
tableRowCol_needExpand ,
#endif
getTableRowColNeedShrink ,
setTableRowColNeedShrink ,
#if defined(ENABLE_OVERLOADING)
tableRowCol_needShrink ,
#endif
getTableRowColRequisition ,
setTableRowColRequisition ,
#if defined(ENABLE_OVERLOADING)
tableRowCol_requisition ,
#endif
getTableRowColShrink ,
setTableRowColShrink ,
#if defined(ENABLE_OVERLOADING)
tableRowCol_shrink ,
#endif
getTableRowColSpacing ,
setTableRowColSpacing ,
#if defined(ENABLE_OVERLOADING)
tableRowCol_spacing ,
#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.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
newtype TableRowCol = TableRowCol (SP.ManagedPtr TableRowCol)
deriving (TableRowCol -> TableRowCol -> Bool
(TableRowCol -> TableRowCol -> Bool)
-> (TableRowCol -> TableRowCol -> Bool) -> Eq TableRowCol
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TableRowCol -> TableRowCol -> Bool
$c/= :: TableRowCol -> TableRowCol -> Bool
== :: TableRowCol -> TableRowCol -> Bool
$c== :: TableRowCol -> TableRowCol -> Bool
Eq)
instance SP.ManagedPtrNewtype TableRowCol where
toManagedPtr :: TableRowCol -> ManagedPtr TableRowCol
toManagedPtr (TableRowCol ManagedPtr TableRowCol
p) = ManagedPtr TableRowCol
p
instance BoxedPtr TableRowCol where
boxedPtrCopy :: TableRowCol -> IO TableRowCol
boxedPtrCopy = \TableRowCol
p -> TableRowCol
-> (Ptr TableRowCol -> IO TableRowCol) -> IO TableRowCol
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TableRowCol
p (Int -> Ptr TableRowCol -> IO (Ptr TableRowCol)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
28 (Ptr TableRowCol -> IO (Ptr TableRowCol))
-> (Ptr TableRowCol -> IO TableRowCol)
-> Ptr TableRowCol
-> IO TableRowCol
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr TableRowCol -> TableRowCol)
-> Ptr TableRowCol -> IO TableRowCol
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr TableRowCol -> TableRowCol
TableRowCol)
boxedPtrFree :: TableRowCol -> IO ()
boxedPtrFree = \TableRowCol
x -> TableRowCol -> (Ptr TableRowCol -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr TableRowCol
x Ptr TableRowCol -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr TableRowCol where
boxedPtrCalloc :: IO (Ptr TableRowCol)
boxedPtrCalloc = Int -> IO (Ptr TableRowCol)
forall a. Int -> IO (Ptr a)
callocBytes Int
28
newZeroTableRowCol :: MonadIO m => m TableRowCol
newZeroTableRowCol :: m TableRowCol
newZeroTableRowCol = IO TableRowCol -> m TableRowCol
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TableRowCol -> m TableRowCol)
-> IO TableRowCol -> m TableRowCol
forall a b. (a -> b) -> a -> b
$ IO (Ptr TableRowCol)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr TableRowCol)
-> (Ptr TableRowCol -> IO TableRowCol) -> IO TableRowCol
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr TableRowCol -> TableRowCol)
-> Ptr TableRowCol -> IO TableRowCol
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr TableRowCol -> TableRowCol
TableRowCol
instance tag ~ 'AttrSet => Constructible TableRowCol tag where
new :: (ManagedPtr TableRowCol -> TableRowCol)
-> [AttrOp TableRowCol tag] -> m TableRowCol
new ManagedPtr TableRowCol -> TableRowCol
_ [AttrOp TableRowCol tag]
attrs = do
TableRowCol
o <- m TableRowCol
forall (m :: * -> *). MonadIO m => m TableRowCol
newZeroTableRowCol
TableRowCol -> [AttrOp TableRowCol 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set TableRowCol
o [AttrOp TableRowCol tag]
[AttrOp TableRowCol 'AttrSet]
attrs
TableRowCol -> m TableRowCol
forall (m :: * -> *) a. Monad m => a -> m a
return TableRowCol
o
getTableRowColRequisition :: MonadIO m => TableRowCol -> m Word16
getTableRowColRequisition :: TableRowCol -> m Word16
getTableRowColRequisition TableRowCol
s = IO Word16 -> m Word16
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ TableRowCol -> (Ptr TableRowCol -> IO Word16) -> IO Word16
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableRowCol
s ((Ptr TableRowCol -> IO Word16) -> IO Word16)
-> (Ptr TableRowCol -> IO Word16) -> IO Word16
forall a b. (a -> b) -> a -> b
$ \Ptr TableRowCol
ptr -> do
Word16
val <- Ptr Word16 -> IO Word16
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableRowCol
ptr Ptr TableRowCol -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO Word16
Word16 -> IO Word16
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
val
setTableRowColRequisition :: MonadIO m => TableRowCol -> Word16 -> m ()
setTableRowColRequisition :: TableRowCol -> Word16 -> m ()
setTableRowColRequisition TableRowCol
s Word16
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableRowCol -> (Ptr TableRowCol -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableRowCol
s ((Ptr TableRowCol -> IO ()) -> IO ())
-> (Ptr TableRowCol -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableRowCol
ptr -> do
Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableRowCol
ptr Ptr TableRowCol -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Word16
val :: Word16)
#if defined(ENABLE_OVERLOADING)
data TableRowColRequisitionFieldInfo
instance AttrInfo TableRowColRequisitionFieldInfo where
type AttrBaseTypeConstraint TableRowColRequisitionFieldInfo = (~) TableRowCol
type AttrAllowedOps TableRowColRequisitionFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TableRowColRequisitionFieldInfo = (~) Word16
type AttrTransferTypeConstraint TableRowColRequisitionFieldInfo = (~)Word16
type AttrTransferType TableRowColRequisitionFieldInfo = Word16
type AttrGetType TableRowColRequisitionFieldInfo = Word16
type AttrLabel TableRowColRequisitionFieldInfo = "requisition"
type AttrOrigin TableRowColRequisitionFieldInfo = TableRowCol
attrGet = getTableRowColRequisition
attrSet = setTableRowColRequisition
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
tableRowCol_requisition :: AttrLabelProxy "requisition"
tableRowCol_requisition = AttrLabelProxy
#endif
getTableRowColAllocation :: MonadIO m => TableRowCol -> m Word16
getTableRowColAllocation :: TableRowCol -> m Word16
getTableRowColAllocation TableRowCol
s = IO Word16 -> m Word16
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ TableRowCol -> (Ptr TableRowCol -> IO Word16) -> IO Word16
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableRowCol
s ((Ptr TableRowCol -> IO Word16) -> IO Word16)
-> (Ptr TableRowCol -> IO Word16) -> IO Word16
forall a b. (a -> b) -> a -> b
$ \Ptr TableRowCol
ptr -> do
Word16
val <- Ptr Word16 -> IO Word16
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableRowCol
ptr Ptr TableRowCol -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
2) :: IO Word16
Word16 -> IO Word16
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
val
setTableRowColAllocation :: MonadIO m => TableRowCol -> Word16 -> m ()
setTableRowColAllocation :: TableRowCol -> Word16 -> m ()
setTableRowColAllocation TableRowCol
s Word16
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableRowCol -> (Ptr TableRowCol -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableRowCol
s ((Ptr TableRowCol -> IO ()) -> IO ())
-> (Ptr TableRowCol -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableRowCol
ptr -> do
Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableRowCol
ptr Ptr TableRowCol -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
2) (Word16
val :: Word16)
#if defined(ENABLE_OVERLOADING)
data TableRowColAllocationFieldInfo
instance AttrInfo TableRowColAllocationFieldInfo where
type AttrBaseTypeConstraint TableRowColAllocationFieldInfo = (~) TableRowCol
type AttrAllowedOps TableRowColAllocationFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TableRowColAllocationFieldInfo = (~) Word16
type AttrTransferTypeConstraint TableRowColAllocationFieldInfo = (~)Word16
type AttrTransferType TableRowColAllocationFieldInfo = Word16
type AttrGetType TableRowColAllocationFieldInfo = Word16
type AttrLabel TableRowColAllocationFieldInfo = "allocation"
type AttrOrigin TableRowColAllocationFieldInfo = TableRowCol
attrGet = getTableRowColAllocation
attrSet = setTableRowColAllocation
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
tableRowCol_allocation :: AttrLabelProxy "allocation"
tableRowCol_allocation = AttrLabelProxy
#endif
getTableRowColSpacing :: MonadIO m => TableRowCol -> m Word16
getTableRowColSpacing :: TableRowCol -> m Word16
getTableRowColSpacing TableRowCol
s = IO Word16 -> m Word16
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ TableRowCol -> (Ptr TableRowCol -> IO Word16) -> IO Word16
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableRowCol
s ((Ptr TableRowCol -> IO Word16) -> IO Word16)
-> (Ptr TableRowCol -> IO Word16) -> IO Word16
forall a b. (a -> b) -> a -> b
$ \Ptr TableRowCol
ptr -> do
Word16
val <- Ptr Word16 -> IO Word16
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableRowCol
ptr Ptr TableRowCol -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) :: IO Word16
Word16 -> IO Word16
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
val
setTableRowColSpacing :: MonadIO m => TableRowCol -> Word16 -> m ()
setTableRowColSpacing :: TableRowCol -> Word16 -> m ()
setTableRowColSpacing TableRowCol
s Word16
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableRowCol -> (Ptr TableRowCol -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableRowCol
s ((Ptr TableRowCol -> IO ()) -> IO ())
-> (Ptr TableRowCol -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableRowCol
ptr -> do
Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableRowCol
ptr Ptr TableRowCol -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) (Word16
val :: Word16)
#if defined(ENABLE_OVERLOADING)
data TableRowColSpacingFieldInfo
instance AttrInfo TableRowColSpacingFieldInfo where
type AttrBaseTypeConstraint TableRowColSpacingFieldInfo = (~) TableRowCol
type AttrAllowedOps TableRowColSpacingFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TableRowColSpacingFieldInfo = (~) Word16
type AttrTransferTypeConstraint TableRowColSpacingFieldInfo = (~)Word16
type AttrTransferType TableRowColSpacingFieldInfo = Word16
type AttrGetType TableRowColSpacingFieldInfo = Word16
type AttrLabel TableRowColSpacingFieldInfo = "spacing"
type AttrOrigin TableRowColSpacingFieldInfo = TableRowCol
attrGet = getTableRowColSpacing
attrSet = setTableRowColSpacing
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
tableRowCol_spacing :: AttrLabelProxy "spacing"
tableRowCol_spacing = AttrLabelProxy
#endif
getTableRowColNeedExpand :: MonadIO m => TableRowCol -> m Word32
getTableRowColNeedExpand :: TableRowCol -> m Word32
getTableRowColNeedExpand TableRowCol
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ TableRowCol -> (Ptr TableRowCol -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableRowCol
s ((Ptr TableRowCol -> IO Word32) -> IO Word32)
-> (Ptr TableRowCol -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr TableRowCol
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableRowCol
ptr Ptr TableRowCol -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setTableRowColNeedExpand :: MonadIO m => TableRowCol -> Word32 -> m ()
setTableRowColNeedExpand :: TableRowCol -> Word32 -> m ()
setTableRowColNeedExpand TableRowCol
s Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableRowCol -> (Ptr TableRowCol -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableRowCol
s ((Ptr TableRowCol -> IO ()) -> IO ())
-> (Ptr TableRowCol -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableRowCol
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableRowCol
ptr Ptr TableRowCol -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data TableRowColNeedExpandFieldInfo
instance AttrInfo TableRowColNeedExpandFieldInfo where
type AttrBaseTypeConstraint TableRowColNeedExpandFieldInfo = (~) TableRowCol
type AttrAllowedOps TableRowColNeedExpandFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TableRowColNeedExpandFieldInfo = (~) Word32
type AttrTransferTypeConstraint TableRowColNeedExpandFieldInfo = (~)Word32
type AttrTransferType TableRowColNeedExpandFieldInfo = Word32
type AttrGetType TableRowColNeedExpandFieldInfo = Word32
type AttrLabel TableRowColNeedExpandFieldInfo = "need_expand"
type AttrOrigin TableRowColNeedExpandFieldInfo = TableRowCol
attrGet = getTableRowColNeedExpand
attrSet = setTableRowColNeedExpand
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
tableRowCol_needExpand :: AttrLabelProxy "needExpand"
tableRowCol_needExpand = AttrLabelProxy
#endif
getTableRowColNeedShrink :: MonadIO m => TableRowCol -> m Word32
getTableRowColNeedShrink :: TableRowCol -> m Word32
getTableRowColNeedShrink TableRowCol
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ TableRowCol -> (Ptr TableRowCol -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableRowCol
s ((Ptr TableRowCol -> IO Word32) -> IO Word32)
-> (Ptr TableRowCol -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr TableRowCol
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableRowCol
ptr Ptr TableRowCol -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setTableRowColNeedShrink :: MonadIO m => TableRowCol -> Word32 -> m ()
setTableRowColNeedShrink :: TableRowCol -> Word32 -> m ()
setTableRowColNeedShrink TableRowCol
s Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableRowCol -> (Ptr TableRowCol -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableRowCol
s ((Ptr TableRowCol -> IO ()) -> IO ())
-> (Ptr TableRowCol -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableRowCol
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableRowCol
ptr Ptr TableRowCol -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data TableRowColNeedShrinkFieldInfo
instance AttrInfo TableRowColNeedShrinkFieldInfo where
type AttrBaseTypeConstraint TableRowColNeedShrinkFieldInfo = (~) TableRowCol
type AttrAllowedOps TableRowColNeedShrinkFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TableRowColNeedShrinkFieldInfo = (~) Word32
type AttrTransferTypeConstraint TableRowColNeedShrinkFieldInfo = (~)Word32
type AttrTransferType TableRowColNeedShrinkFieldInfo = Word32
type AttrGetType TableRowColNeedShrinkFieldInfo = Word32
type AttrLabel TableRowColNeedShrinkFieldInfo = "need_shrink"
type AttrOrigin TableRowColNeedShrinkFieldInfo = TableRowCol
attrGet = getTableRowColNeedShrink
attrSet = setTableRowColNeedShrink
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
tableRowCol_needShrink :: AttrLabelProxy "needShrink"
tableRowCol_needShrink = AttrLabelProxy
#endif
getTableRowColExpand :: MonadIO m => TableRowCol -> m Word32
getTableRowColExpand :: TableRowCol -> m Word32
getTableRowColExpand TableRowCol
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ TableRowCol -> (Ptr TableRowCol -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableRowCol
s ((Ptr TableRowCol -> IO Word32) -> IO Word32)
-> (Ptr TableRowCol -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr TableRowCol
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableRowCol
ptr Ptr TableRowCol -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setTableRowColExpand :: MonadIO m => TableRowCol -> Word32 -> m ()
setTableRowColExpand :: TableRowCol -> Word32 -> m ()
setTableRowColExpand TableRowCol
s Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableRowCol -> (Ptr TableRowCol -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableRowCol
s ((Ptr TableRowCol -> IO ()) -> IO ())
-> (Ptr TableRowCol -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableRowCol
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableRowCol
ptr Ptr TableRowCol -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data TableRowColExpandFieldInfo
instance AttrInfo TableRowColExpandFieldInfo where
type AttrBaseTypeConstraint TableRowColExpandFieldInfo = (~) TableRowCol
type AttrAllowedOps TableRowColExpandFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TableRowColExpandFieldInfo = (~) Word32
type AttrTransferTypeConstraint TableRowColExpandFieldInfo = (~)Word32
type AttrTransferType TableRowColExpandFieldInfo = Word32
type AttrGetType TableRowColExpandFieldInfo = Word32
type AttrLabel TableRowColExpandFieldInfo = "expand"
type AttrOrigin TableRowColExpandFieldInfo = TableRowCol
attrGet = getTableRowColExpand
attrSet = setTableRowColExpand
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
tableRowCol_expand :: AttrLabelProxy "expand"
tableRowCol_expand = AttrLabelProxy
#endif
getTableRowColShrink :: MonadIO m => TableRowCol -> m Word32
getTableRowColShrink :: TableRowCol -> m Word32
getTableRowColShrink TableRowCol
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ TableRowCol -> (Ptr TableRowCol -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableRowCol
s ((Ptr TableRowCol -> IO Word32) -> IO Word32)
-> (Ptr TableRowCol -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr TableRowCol
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableRowCol
ptr Ptr TableRowCol -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setTableRowColShrink :: MonadIO m => TableRowCol -> Word32 -> m ()
setTableRowColShrink :: TableRowCol -> Word32 -> m ()
setTableRowColShrink TableRowCol
s Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableRowCol -> (Ptr TableRowCol -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableRowCol
s ((Ptr TableRowCol -> IO ()) -> IO ())
-> (Ptr TableRowCol -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableRowCol
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableRowCol
ptr Ptr TableRowCol -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data TableRowColShrinkFieldInfo
instance AttrInfo TableRowColShrinkFieldInfo where
type AttrBaseTypeConstraint TableRowColShrinkFieldInfo = (~) TableRowCol
type AttrAllowedOps TableRowColShrinkFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TableRowColShrinkFieldInfo = (~) Word32
type AttrTransferTypeConstraint TableRowColShrinkFieldInfo = (~)Word32
type AttrTransferType TableRowColShrinkFieldInfo = Word32
type AttrGetType TableRowColShrinkFieldInfo = Word32
type AttrLabel TableRowColShrinkFieldInfo = "shrink"
type AttrOrigin TableRowColShrinkFieldInfo = TableRowCol
attrGet = getTableRowColShrink
attrSet = setTableRowColShrink
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
tableRowCol_shrink :: AttrLabelProxy "shrink"
tableRowCol_shrink = AttrLabelProxy
#endif
getTableRowColEmpty :: MonadIO m => TableRowCol -> m Word32
getTableRowColEmpty :: TableRowCol -> m Word32
getTableRowColEmpty TableRowCol
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ TableRowCol -> (Ptr TableRowCol -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableRowCol
s ((Ptr TableRowCol -> IO Word32) -> IO Word32)
-> (Ptr TableRowCol -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr TableRowCol
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableRowCol
ptr Ptr TableRowCol -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setTableRowColEmpty :: MonadIO m => TableRowCol -> Word32 -> m ()
setTableRowColEmpty :: TableRowCol -> Word32 -> m ()
setTableRowColEmpty TableRowCol
s Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableRowCol -> (Ptr TableRowCol -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableRowCol
s ((Ptr TableRowCol -> IO ()) -> IO ())
-> (Ptr TableRowCol -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableRowCol
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableRowCol
ptr Ptr TableRowCol -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data TableRowColEmptyFieldInfo
instance AttrInfo TableRowColEmptyFieldInfo where
type AttrBaseTypeConstraint TableRowColEmptyFieldInfo = (~) TableRowCol
type AttrAllowedOps TableRowColEmptyFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TableRowColEmptyFieldInfo = (~) Word32
type AttrTransferTypeConstraint TableRowColEmptyFieldInfo = (~)Word32
type AttrTransferType TableRowColEmptyFieldInfo = Word32
type AttrGetType TableRowColEmptyFieldInfo = Word32
type AttrLabel TableRowColEmptyFieldInfo = "empty"
type AttrOrigin TableRowColEmptyFieldInfo = TableRowCol
attrGet = getTableRowColEmpty
attrSet = setTableRowColEmpty
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
tableRowCol_empty :: AttrLabelProxy "empty"
tableRowCol_empty = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TableRowCol
type instance O.AttributeList TableRowCol = TableRowColAttributeList
type TableRowColAttributeList = ('[ '("requisition", TableRowColRequisitionFieldInfo), '("allocation", TableRowColAllocationFieldInfo), '("spacing", TableRowColSpacingFieldInfo), '("needExpand", TableRowColNeedExpandFieldInfo), '("needShrink", TableRowColNeedShrinkFieldInfo), '("expand", TableRowColExpandFieldInfo), '("shrink", TableRowColShrinkFieldInfo), '("empty", TableRowColEmptyFieldInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveTableRowColMethod (t :: Symbol) (o :: *) :: * where
ResolveTableRowColMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTableRowColMethod t TableRowCol, O.MethodInfo info TableRowCol p) => OL.IsLabel t (TableRowCol -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif