#define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \
       && !defined(__HADDOCK_VERSION__))
module GI.Atk.Structs.TextRectangle
    (
    TextRectangle(..)                       ,
    newZeroTextRectangle                    ,
    noTextRectangle                         ,
 
    getTextRectangleHeight                  ,
    setTextRectangleHeight                  ,
#if ENABLE_OVERLOADING
    textRectangle_height                    ,
#endif
    getTextRectangleWidth                   ,
    setTextRectangleWidth                   ,
#if ENABLE_OVERLOADING
    textRectangle_width                     ,
#endif
    getTextRectangleX                       ,
    setTextRectangleX                       ,
#if ENABLE_OVERLOADING
    textRectangle_x                         ,
#endif
    getTextRectangleY                       ,
    setTextRectangleY                       ,
#if ENABLE_OVERLOADING
    textRectangle_y                         ,
#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.ManagedPtr as B.ManagedPtr
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.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
newtype TextRectangle = TextRectangle (ManagedPtr TextRectangle)
instance WrappedPtr TextRectangle where
    wrappedPtrCalloc = callocBytes 16
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 16 >=> wrapPtr TextRectangle)
    wrappedPtrFree = Just ptr_to_g_free
newZeroTextRectangle :: MonadIO m => m TextRectangle
newZeroTextRectangle = liftIO $ wrappedPtrCalloc >>= wrapPtr TextRectangle
instance tag ~ 'AttrSet => Constructible TextRectangle tag where
    new _ attrs = do
        o <- newZeroTextRectangle
        GI.Attributes.set o attrs
        return o
noTextRectangle :: Maybe TextRectangle
noTextRectangle = Nothing
getTextRectangleX :: MonadIO m => TextRectangle -> m Int32
getTextRectangleX s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO Int32
    return val
setTextRectangleX :: MonadIO m => TextRectangle -> Int32 -> m ()
setTextRectangleX s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: Int32)
#if ENABLE_OVERLOADING
data TextRectangleXFieldInfo
instance AttrInfo TextRectangleXFieldInfo where
    type AttrAllowedOps TextRectangleXFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextRectangleXFieldInfo = (~) Int32
    type AttrBaseTypeConstraint TextRectangleXFieldInfo = (~) TextRectangle
    type AttrGetType TextRectangleXFieldInfo = Int32
    type AttrLabel TextRectangleXFieldInfo = "x"
    type AttrOrigin TextRectangleXFieldInfo = TextRectangle
    attrGet _ = getTextRectangleX
    attrSet _ = setTextRectangleX
    attrConstruct = undefined
    attrClear _ = undefined
textRectangle_x :: AttrLabelProxy "x"
textRectangle_x = AttrLabelProxy
#endif
getTextRectangleY :: MonadIO m => TextRectangle -> m Int32
getTextRectangleY s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 4) :: IO Int32
    return val
setTextRectangleY :: MonadIO m => TextRectangle -> Int32 -> m ()
setTextRectangleY s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 4) (val :: Int32)
#if ENABLE_OVERLOADING
data TextRectangleYFieldInfo
instance AttrInfo TextRectangleYFieldInfo where
    type AttrAllowedOps TextRectangleYFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextRectangleYFieldInfo = (~) Int32
    type AttrBaseTypeConstraint TextRectangleYFieldInfo = (~) TextRectangle
    type AttrGetType TextRectangleYFieldInfo = Int32
    type AttrLabel TextRectangleYFieldInfo = "y"
    type AttrOrigin TextRectangleYFieldInfo = TextRectangle
    attrGet _ = getTextRectangleY
    attrSet _ = setTextRectangleY
    attrConstruct = undefined
    attrClear _ = undefined
textRectangle_y :: AttrLabelProxy "y"
textRectangle_y = AttrLabelProxy
#endif
getTextRectangleWidth :: MonadIO m => TextRectangle -> m Int32
getTextRectangleWidth s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO Int32
    return val
setTextRectangleWidth :: MonadIO m => TextRectangle -> Int32 -> m ()
setTextRectangleWidth s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: Int32)
#if ENABLE_OVERLOADING
data TextRectangleWidthFieldInfo
instance AttrInfo TextRectangleWidthFieldInfo where
    type AttrAllowedOps TextRectangleWidthFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextRectangleWidthFieldInfo = (~) Int32
    type AttrBaseTypeConstraint TextRectangleWidthFieldInfo = (~) TextRectangle
    type AttrGetType TextRectangleWidthFieldInfo = Int32
    type AttrLabel TextRectangleWidthFieldInfo = "width"
    type AttrOrigin TextRectangleWidthFieldInfo = TextRectangle
    attrGet _ = getTextRectangleWidth
    attrSet _ = setTextRectangleWidth
    attrConstruct = undefined
    attrClear _ = undefined
textRectangle_width :: AttrLabelProxy "width"
textRectangle_width = AttrLabelProxy
#endif
getTextRectangleHeight :: MonadIO m => TextRectangle -> m Int32
getTextRectangleHeight s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 12) :: IO Int32
    return val
setTextRectangleHeight :: MonadIO m => TextRectangle -> Int32 -> m ()
setTextRectangleHeight s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 12) (val :: Int32)
#if ENABLE_OVERLOADING
data TextRectangleHeightFieldInfo
instance AttrInfo TextRectangleHeightFieldInfo where
    type AttrAllowedOps TextRectangleHeightFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextRectangleHeightFieldInfo = (~) Int32
    type AttrBaseTypeConstraint TextRectangleHeightFieldInfo = (~) TextRectangle
    type AttrGetType TextRectangleHeightFieldInfo = Int32
    type AttrLabel TextRectangleHeightFieldInfo = "height"
    type AttrOrigin TextRectangleHeightFieldInfo = TextRectangle
    attrGet _ = getTextRectangleHeight
    attrSet _ = setTextRectangleHeight
    attrConstruct = undefined
    attrClear _ = undefined
textRectangle_height :: AttrLabelProxy "height"
textRectangle_height = AttrLabelProxy
#endif
#if ENABLE_OVERLOADING
instance O.HasAttributeList TextRectangle
type instance O.AttributeList TextRectangle = TextRectangleAttributeList
type TextRectangleAttributeList = ('[ '("x", TextRectangleXFieldInfo), '("y", TextRectangleYFieldInfo), '("width", TextRectangleWidthFieldInfo), '("height", TextRectangleHeightFieldInfo)] :: [(Symbol, *)])
#endif
#if ENABLE_OVERLOADING
type family ResolveTextRectangleMethod (t :: Symbol) (o :: *) :: * where
    ResolveTextRectangleMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTextRectangleMethod t TextRectangle, O.MethodInfo info TextRectangle p) => O.IsLabelProxy t (TextRectangle -> p) where
    fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveTextRectangleMethod t TextRectangle, O.MethodInfo info TextRectangle p) => O.IsLabel t (TextRectangle -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#else
    fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif
#endif
#endif