{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GtkFixed@ places its child widgets at fixed positions and with fixed sizes.
-- 
-- @GtkFixed@ performs no automatic layout management.
-- 
-- For most applications, you should not use this container! It keeps
-- you from having to learn about the other GTK containers, but it
-- results in broken applications.  With @GtkFixed@, the following
-- things will result in truncated text, overlapping widgets, and
-- other display bugs:
-- 
-- * Themes, which may change widget sizes.
-- * Fonts other than the one you used to write the app will of course
-- change the size of widgets containing text; keep in mind that
-- users may use a larger font because of difficulty reading the
-- default, or they may be using a different OS that provides different fonts.
-- * Translation of text into other languages changes its size. Also,
-- display of non-English text will use a different font in many
-- cases.
-- 
-- 
-- In addition, @GtkFixed@ does not pay attention to text direction and
-- thus may produce unwanted results if your app is run under right-to-left
-- languages such as Hebrew or Arabic. That is: normally GTK will order
-- containers appropriately for the text direction, e.g. to put labels to
-- the right of the thing they label when using an RTL language, but it can’t
-- do that with @GtkFixed@. So if you need to reorder widgets depending on
-- the text direction, you would need to manually detect it and adjust child
-- positions accordingly.
-- 
-- Finally, fixed positioning makes it kind of annoying to add\/remove
-- UI elements, since you have to reposition all the other elements. This
-- is a long-term maintenance problem for your application.
-- 
-- If you know none of these things are an issue for your application,
-- and prefer the simplicity of @GtkFixed@, by all means use the
-- widget. But you should be aware of the tradeoffs.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Gtk.Objects.Fixed
    ( 

-- * Exported types
    Fixed(..)                               ,
    IsFixed                                 ,
    toFixed                                 ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [actionSetEnabled]("GI.Gtk.Objects.Widget#g:method:actionSetEnabled"), [activate]("GI.Gtk.Objects.Widget#g:method:activate"), [activateAction]("GI.Gtk.Objects.Widget#g:method:activateAction"), [activateDefault]("GI.Gtk.Objects.Widget#g:method:activateDefault"), [addController]("GI.Gtk.Objects.Widget#g:method:addController"), [addCssClass]("GI.Gtk.Objects.Widget#g:method:addCssClass"), [addMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:addMnemonicLabel"), [addTickCallback]("GI.Gtk.Objects.Widget#g:method:addTickCallback"), [allocate]("GI.Gtk.Objects.Widget#g:method:allocate"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [childFocus]("GI.Gtk.Objects.Widget#g:method:childFocus"), [computeBounds]("GI.Gtk.Objects.Widget#g:method:computeBounds"), [computeExpand]("GI.Gtk.Objects.Widget#g:method:computeExpand"), [computePoint]("GI.Gtk.Objects.Widget#g:method:computePoint"), [computeTransform]("GI.Gtk.Objects.Widget#g:method:computeTransform"), [contains]("GI.Gtk.Objects.Widget#g:method:contains"), [createPangoContext]("GI.Gtk.Objects.Widget#g:method:createPangoContext"), [createPangoLayout]("GI.Gtk.Objects.Widget#g:method:createPangoLayout"), [disposeTemplate]("GI.Gtk.Objects.Widget#g:method:disposeTemplate"), [dragCheckThreshold]("GI.Gtk.Objects.Widget#g:method:dragCheckThreshold"), [errorBell]("GI.Gtk.Objects.Widget#g:method:errorBell"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [grabFocus]("GI.Gtk.Objects.Widget#g:method:grabFocus"), [hasCssClass]("GI.Gtk.Objects.Widget#g:method:hasCssClass"), [hasDefault]("GI.Gtk.Objects.Widget#g:method:hasDefault"), [hasFocus]("GI.Gtk.Objects.Widget#g:method:hasFocus"), [hasVisibleFocus]("GI.Gtk.Objects.Widget#g:method:hasVisibleFocus"), [hide]("GI.Gtk.Objects.Widget#g:method:hide"), [inDestruction]("GI.Gtk.Objects.Widget#g:method:inDestruction"), [initTemplate]("GI.Gtk.Objects.Widget#g:method:initTemplate"), [insertActionGroup]("GI.Gtk.Objects.Widget#g:method:insertActionGroup"), [insertAfter]("GI.Gtk.Objects.Widget#g:method:insertAfter"), [insertBefore]("GI.Gtk.Objects.Widget#g:method:insertBefore"), [isAncestor]("GI.Gtk.Objects.Widget#g:method:isAncestor"), [isDrawable]("GI.Gtk.Objects.Widget#g:method:isDrawable"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isFocus]("GI.Gtk.Objects.Widget#g:method:isFocus"), [isSensitive]("GI.Gtk.Objects.Widget#g:method:isSensitive"), [isVisible]("GI.Gtk.Objects.Widget#g:method:isVisible"), [keynavFailed]("GI.Gtk.Objects.Widget#g:method:keynavFailed"), [listMnemonicLabels]("GI.Gtk.Objects.Widget#g:method:listMnemonicLabels"), [map]("GI.Gtk.Objects.Widget#g:method:map"), [measure]("GI.Gtk.Objects.Widget#g:method:measure"), [mnemonicActivate]("GI.Gtk.Objects.Widget#g:method:mnemonicActivate"), [move]("GI.Gtk.Objects.Fixed#g:method:move"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [observeChildren]("GI.Gtk.Objects.Widget#g:method:observeChildren"), [observeControllers]("GI.Gtk.Objects.Widget#g:method:observeControllers"), [pick]("GI.Gtk.Objects.Widget#g:method:pick"), [put]("GI.Gtk.Objects.Fixed#g:method:put"), [queueAllocate]("GI.Gtk.Objects.Widget#g:method:queueAllocate"), [queueDraw]("GI.Gtk.Objects.Widget#g:method:queueDraw"), [queueResize]("GI.Gtk.Objects.Widget#g:method:queueResize"), [realize]("GI.Gtk.Objects.Widget#g:method:realize"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [remove]("GI.Gtk.Objects.Fixed#g:method:remove"), [removeController]("GI.Gtk.Objects.Widget#g:method:removeController"), [removeCssClass]("GI.Gtk.Objects.Widget#g:method:removeCssClass"), [removeMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:removeMnemonicLabel"), [removeTickCallback]("GI.Gtk.Objects.Widget#g:method:removeTickCallback"), [resetProperty]("GI.Gtk.Interfaces.Accessible#g:method:resetProperty"), [resetRelation]("GI.Gtk.Interfaces.Accessible#g:method:resetRelation"), [resetState]("GI.Gtk.Interfaces.Accessible#g:method:resetState"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [shouldLayout]("GI.Gtk.Objects.Widget#g:method:shouldLayout"), [show]("GI.Gtk.Objects.Widget#g:method:show"), [sizeAllocate]("GI.Gtk.Objects.Widget#g:method:sizeAllocate"), [snapshotChild]("GI.Gtk.Objects.Widget#g:method:snapshotChild"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [translateCoordinates]("GI.Gtk.Objects.Widget#g:method:translateCoordinates"), [triggerTooltipQuery]("GI.Gtk.Objects.Widget#g:method:triggerTooltipQuery"), [unmap]("GI.Gtk.Objects.Widget#g:method:unmap"), [unparent]("GI.Gtk.Objects.Widget#g:method:unparent"), [unrealize]("GI.Gtk.Objects.Widget#g:method:unrealize"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unsetStateFlags]("GI.Gtk.Objects.Widget#g:method:unsetStateFlags"), [updateNextAccessibleSibling]("GI.Gtk.Interfaces.Accessible#g:method:updateNextAccessibleSibling"), [updateProperty]("GI.Gtk.Interfaces.Accessible#g:method:updateProperty"), [updateRelation]("GI.Gtk.Interfaces.Accessible#g:method:updateRelation"), [updateState]("GI.Gtk.Interfaces.Accessible#g:method:updateState"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAccessibleParent]("GI.Gtk.Interfaces.Accessible#g:method:getAccessibleParent"), [getAccessibleRole]("GI.Gtk.Interfaces.Accessible#g:method:getAccessibleRole"), [getAllocatedBaseline]("GI.Gtk.Objects.Widget#g:method:getAllocatedBaseline"), [getAllocatedHeight]("GI.Gtk.Objects.Widget#g:method:getAllocatedHeight"), [getAllocatedWidth]("GI.Gtk.Objects.Widget#g:method:getAllocatedWidth"), [getAllocation]("GI.Gtk.Objects.Widget#g:method:getAllocation"), [getAncestor]("GI.Gtk.Objects.Widget#g:method:getAncestor"), [getAtContext]("GI.Gtk.Interfaces.Accessible#g:method:getAtContext"), [getBounds]("GI.Gtk.Interfaces.Accessible#g:method:getBounds"), [getBuildableId]("GI.Gtk.Interfaces.Buildable#g:method:getBuildableId"), [getCanFocus]("GI.Gtk.Objects.Widget#g:method:getCanFocus"), [getCanTarget]("GI.Gtk.Objects.Widget#g:method:getCanTarget"), [getChildPosition]("GI.Gtk.Objects.Fixed#g:method:getChildPosition"), [getChildTransform]("GI.Gtk.Objects.Fixed#g:method:getChildTransform"), [getChildVisible]("GI.Gtk.Objects.Widget#g:method:getChildVisible"), [getClipboard]("GI.Gtk.Objects.Widget#g:method:getClipboard"), [getColor]("GI.Gtk.Objects.Widget#g:method:getColor"), [getCssClasses]("GI.Gtk.Objects.Widget#g:method:getCssClasses"), [getCssName]("GI.Gtk.Objects.Widget#g:method:getCssName"), [getCursor]("GI.Gtk.Objects.Widget#g:method:getCursor"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDirection]("GI.Gtk.Objects.Widget#g:method:getDirection"), [getDisplay]("GI.Gtk.Objects.Widget#g:method:getDisplay"), [getFirstAccessibleChild]("GI.Gtk.Interfaces.Accessible#g:method:getFirstAccessibleChild"), [getFirstChild]("GI.Gtk.Objects.Widget#g:method:getFirstChild"), [getFocusChild]("GI.Gtk.Objects.Widget#g:method:getFocusChild"), [getFocusOnClick]("GI.Gtk.Objects.Widget#g:method:getFocusOnClick"), [getFocusable]("GI.Gtk.Objects.Widget#g:method:getFocusable"), [getFontMap]("GI.Gtk.Objects.Widget#g:method:getFontMap"), [getFontOptions]("GI.Gtk.Objects.Widget#g:method:getFontOptions"), [getFrameClock]("GI.Gtk.Objects.Widget#g:method:getFrameClock"), [getHalign]("GI.Gtk.Objects.Widget#g:method:getHalign"), [getHasTooltip]("GI.Gtk.Objects.Widget#g:method:getHasTooltip"), [getHeight]("GI.Gtk.Objects.Widget#g:method:getHeight"), [getHexpand]("GI.Gtk.Objects.Widget#g:method:getHexpand"), [getHexpandSet]("GI.Gtk.Objects.Widget#g:method:getHexpandSet"), [getLastChild]("GI.Gtk.Objects.Widget#g:method:getLastChild"), [getLayoutManager]("GI.Gtk.Objects.Widget#g:method:getLayoutManager"), [getMapped]("GI.Gtk.Objects.Widget#g:method:getMapped"), [getMarginBottom]("GI.Gtk.Objects.Widget#g:method:getMarginBottom"), [getMarginEnd]("GI.Gtk.Objects.Widget#g:method:getMarginEnd"), [getMarginStart]("GI.Gtk.Objects.Widget#g:method:getMarginStart"), [getMarginTop]("GI.Gtk.Objects.Widget#g:method:getMarginTop"), [getName]("GI.Gtk.Objects.Widget#g:method:getName"), [getNative]("GI.Gtk.Objects.Widget#g:method:getNative"), [getNextAccessibleSibling]("GI.Gtk.Interfaces.Accessible#g:method:getNextAccessibleSibling"), [getNextSibling]("GI.Gtk.Objects.Widget#g:method:getNextSibling"), [getOpacity]("GI.Gtk.Objects.Widget#g:method:getOpacity"), [getOverflow]("GI.Gtk.Objects.Widget#g:method:getOverflow"), [getPangoContext]("GI.Gtk.Objects.Widget#g:method:getPangoContext"), [getParent]("GI.Gtk.Objects.Widget#g:method:getParent"), [getPlatformState]("GI.Gtk.Interfaces.Accessible#g:method:getPlatformState"), [getPreferredSize]("GI.Gtk.Objects.Widget#g:method:getPreferredSize"), [getPrevSibling]("GI.Gtk.Objects.Widget#g:method:getPrevSibling"), [getPrimaryClipboard]("GI.Gtk.Objects.Widget#g:method:getPrimaryClipboard"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRealized]("GI.Gtk.Objects.Widget#g:method:getRealized"), [getReceivesDefault]("GI.Gtk.Objects.Widget#g:method:getReceivesDefault"), [getRequestMode]("GI.Gtk.Objects.Widget#g:method:getRequestMode"), [getRoot]("GI.Gtk.Objects.Widget#g:method:getRoot"), [getScaleFactor]("GI.Gtk.Objects.Widget#g:method:getScaleFactor"), [getSensitive]("GI.Gtk.Objects.Widget#g:method:getSensitive"), [getSettings]("GI.Gtk.Objects.Widget#g:method:getSettings"), [getSize]("GI.Gtk.Objects.Widget#g:method:getSize"), [getSizeRequest]("GI.Gtk.Objects.Widget#g:method:getSizeRequest"), [getStateFlags]("GI.Gtk.Objects.Widget#g:method:getStateFlags"), [getStyleContext]("GI.Gtk.Objects.Widget#g:method:getStyleContext"), [getTemplateChild]("GI.Gtk.Objects.Widget#g:method:getTemplateChild"), [getTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:getTooltipMarkup"), [getTooltipText]("GI.Gtk.Objects.Widget#g:method:getTooltipText"), [getValign]("GI.Gtk.Objects.Widget#g:method:getValign"), [getVexpand]("GI.Gtk.Objects.Widget#g:method:getVexpand"), [getVexpandSet]("GI.Gtk.Objects.Widget#g:method:getVexpandSet"), [getVisible]("GI.Gtk.Objects.Widget#g:method:getVisible"), [getWidth]("GI.Gtk.Objects.Widget#g:method:getWidth").
-- 
-- ==== Setters
-- [setAccessibleParent]("GI.Gtk.Interfaces.Accessible#g:method:setAccessibleParent"), [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setCanTarget]("GI.Gtk.Objects.Widget#g:method:setCanTarget"), [setChildTransform]("GI.Gtk.Objects.Fixed#g:method:setChildTransform"), [setChildVisible]("GI.Gtk.Objects.Widget#g:method:setChildVisible"), [setCssClasses]("GI.Gtk.Objects.Widget#g:method:setCssClasses"), [setCursor]("GI.Gtk.Objects.Widget#g:method:setCursor"), [setCursorFromName]("GI.Gtk.Objects.Widget#g:method:setCursorFromName"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDirection]("GI.Gtk.Objects.Widget#g:method:setDirection"), [setFocusChild]("GI.Gtk.Objects.Widget#g:method:setFocusChild"), [setFocusOnClick]("GI.Gtk.Objects.Widget#g:method:setFocusOnClick"), [setFocusable]("GI.Gtk.Objects.Widget#g:method:setFocusable"), [setFontMap]("GI.Gtk.Objects.Widget#g:method:setFontMap"), [setFontOptions]("GI.Gtk.Objects.Widget#g:method:setFontOptions"), [setHalign]("GI.Gtk.Objects.Widget#g:method:setHalign"), [setHasTooltip]("GI.Gtk.Objects.Widget#g:method:setHasTooltip"), [setHexpand]("GI.Gtk.Objects.Widget#g:method:setHexpand"), [setHexpandSet]("GI.Gtk.Objects.Widget#g:method:setHexpandSet"), [setLayoutManager]("GI.Gtk.Objects.Widget#g:method:setLayoutManager"), [setMarginBottom]("GI.Gtk.Objects.Widget#g:method:setMarginBottom"), [setMarginEnd]("GI.Gtk.Objects.Widget#g:method:setMarginEnd"), [setMarginStart]("GI.Gtk.Objects.Widget#g:method:setMarginStart"), [setMarginTop]("GI.Gtk.Objects.Widget#g:method:setMarginTop"), [setName]("GI.Gtk.Objects.Widget#g:method:setName"), [setOpacity]("GI.Gtk.Objects.Widget#g:method:setOpacity"), [setOverflow]("GI.Gtk.Objects.Widget#g:method:setOverflow"), [setParent]("GI.Gtk.Objects.Widget#g:method:setParent"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setReceivesDefault]("GI.Gtk.Objects.Widget#g:method:setReceivesDefault"), [setSensitive]("GI.Gtk.Objects.Widget#g:method:setSensitive"), [setSizeRequest]("GI.Gtk.Objects.Widget#g:method:setSizeRequest"), [setStateFlags]("GI.Gtk.Objects.Widget#g:method:setStateFlags"), [setTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:setTooltipMarkup"), [setTooltipText]("GI.Gtk.Objects.Widget#g:method:setTooltipText"), [setValign]("GI.Gtk.Objects.Widget#g:method:setValign"), [setVexpand]("GI.Gtk.Objects.Widget#g:method:setVexpand"), [setVexpandSet]("GI.Gtk.Objects.Widget#g:method:setVexpandSet"), [setVisible]("GI.Gtk.Objects.Widget#g:method:setVisible").

#if defined(ENABLE_OVERLOADING)
    ResolveFixedMethod                      ,
#endif

-- ** getChildPosition #method:getChildPosition#

#if defined(ENABLE_OVERLOADING)
    FixedGetChildPositionMethodInfo         ,
#endif
    fixedGetChildPosition                   ,


-- ** getChildTransform #method:getChildTransform#

#if defined(ENABLE_OVERLOADING)
    FixedGetChildTransformMethodInfo        ,
#endif
    fixedGetChildTransform                  ,


-- ** move #method:move#

#if defined(ENABLE_OVERLOADING)
    FixedMoveMethodInfo                     ,
#endif
    fixedMove                               ,


-- ** new #method:new#

    fixedNew                                ,


-- ** put #method:put#

#if defined(ENABLE_OVERLOADING)
    FixedPutMethodInfo                      ,
#endif
    fixedPut                                ,


-- ** remove #method:remove#

#if defined(ENABLE_OVERLOADING)
    FixedRemoveMethodInfo                   ,
#endif
    fixedRemove                             ,


-- ** setChildTransform #method:setChildTransform#

#if defined(ENABLE_OVERLOADING)
    FixedSetChildTransformMethodInfo        ,
#endif
    fixedSetChildTransform                  ,




    ) 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 GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gsk.Structs.Transform as Gsk.Transform
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

-- | Memory-managed wrapper type.
newtype Fixed = Fixed (SP.ManagedPtr Fixed)
    deriving (Fixed -> Fixed -> Bool
(Fixed -> Fixed -> Bool) -> (Fixed -> Fixed -> Bool) -> Eq Fixed
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Fixed -> Fixed -> Bool
== :: Fixed -> Fixed -> Bool
$c/= :: Fixed -> Fixed -> Bool
/= :: Fixed -> Fixed -> Bool
Eq)

instance SP.ManagedPtrNewtype Fixed where
    toManagedPtr :: Fixed -> ManagedPtr Fixed
toManagedPtr (Fixed ManagedPtr Fixed
p) = ManagedPtr Fixed
p

foreign import ccall "gtk_fixed_get_type"
    c_gtk_fixed_get_type :: IO B.Types.GType

instance B.Types.TypedObject Fixed where
    glibType :: IO GType
glibType = IO GType
c_gtk_fixed_get_type

instance B.Types.GObject Fixed

-- | Type class for types which can be safely cast to `Fixed`, for instance with `toFixed`.
class (SP.GObject o, O.IsDescendantOf Fixed o) => IsFixed o
instance (SP.GObject o, O.IsDescendantOf Fixed o) => IsFixed o

instance O.HasParentTypes Fixed
type instance O.ParentTypes Fixed = '[Gtk.Widget.Widget, GObject.Object.Object, Gtk.Accessible.Accessible, Gtk.Buildable.Buildable, Gtk.ConstraintTarget.ConstraintTarget]

-- | Cast to `Fixed`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toFixed :: (MIO.MonadIO m, IsFixed o) => o -> m Fixed
toFixed :: forall (m :: * -> *) o. (MonadIO m, IsFixed o) => o -> m Fixed
toFixed = IO Fixed -> m Fixed
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Fixed -> m Fixed) -> (o -> IO Fixed) -> o -> m Fixed
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Fixed -> Fixed) -> o -> IO Fixed
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Fixed -> Fixed
Fixed

-- | Convert 'Fixed' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe Fixed) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_fixed_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Fixed -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Fixed
P.Nothing = Ptr GValue -> Ptr Fixed -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Fixed
forall a. Ptr a
FP.nullPtr :: FP.Ptr Fixed)
    gvalueSet_ Ptr GValue
gv (P.Just Fixed
obj) = Fixed -> (Ptr Fixed -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Fixed
obj (Ptr GValue -> Ptr Fixed -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Fixed)
gvalueGet_ Ptr GValue
gv = do
        Ptr Fixed
ptr <- Ptr GValue -> IO (Ptr Fixed)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Fixed)
        if Ptr Fixed
ptr Ptr Fixed -> Ptr Fixed -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Fixed
forall a. Ptr a
FP.nullPtr
        then Fixed -> Maybe Fixed
forall a. a -> Maybe a
P.Just (Fixed -> Maybe Fixed) -> IO Fixed -> IO (Maybe Fixed)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Fixed -> Fixed) -> Ptr Fixed -> IO Fixed
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Fixed -> Fixed
Fixed Ptr Fixed
ptr
        else Maybe Fixed -> IO (Maybe Fixed)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Fixed
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveFixedMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveFixedMethod "actionSetEnabled" o = Gtk.Widget.WidgetActionSetEnabledMethodInfo
    ResolveFixedMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveFixedMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveFixedMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveFixedMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveFixedMethod "addCssClass" o = Gtk.Widget.WidgetAddCssClassMethodInfo
    ResolveFixedMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveFixedMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveFixedMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    ResolveFixedMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveFixedMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveFixedMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveFixedMethod "computeBounds" o = Gtk.Widget.WidgetComputeBoundsMethodInfo
    ResolveFixedMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveFixedMethod "computePoint" o = Gtk.Widget.WidgetComputePointMethodInfo
    ResolveFixedMethod "computeTransform" o = Gtk.Widget.WidgetComputeTransformMethodInfo
    ResolveFixedMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveFixedMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveFixedMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveFixedMethod "disposeTemplate" o = Gtk.Widget.WidgetDisposeTemplateMethodInfo
    ResolveFixedMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveFixedMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveFixedMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveFixedMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveFixedMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveFixedMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveFixedMethod "hasCssClass" o = Gtk.Widget.WidgetHasCssClassMethodInfo
    ResolveFixedMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveFixedMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveFixedMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveFixedMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveFixedMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveFixedMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveFixedMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveFixedMethod "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveFixedMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    ResolveFixedMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveFixedMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveFixedMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveFixedMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveFixedMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveFixedMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveFixedMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveFixedMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveFixedMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveFixedMethod "measure" o = Gtk.Widget.WidgetMeasureMethodInfo
    ResolveFixedMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveFixedMethod "move" o = FixedMoveMethodInfo
    ResolveFixedMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveFixedMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveFixedMethod "observeChildren" o = Gtk.Widget.WidgetObserveChildrenMethodInfo
    ResolveFixedMethod "observeControllers" o = Gtk.Widget.WidgetObserveControllersMethodInfo
    ResolveFixedMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveFixedMethod "put" o = FixedPutMethodInfo
    ResolveFixedMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveFixedMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveFixedMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveFixedMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveFixedMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveFixedMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveFixedMethod "remove" o = FixedRemoveMethodInfo
    ResolveFixedMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveFixedMethod "removeCssClass" o = Gtk.Widget.WidgetRemoveCssClassMethodInfo
    ResolveFixedMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveFixedMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveFixedMethod "resetProperty" o = Gtk.Accessible.AccessibleResetPropertyMethodInfo
    ResolveFixedMethod "resetRelation" o = Gtk.Accessible.AccessibleResetRelationMethodInfo
    ResolveFixedMethod "resetState" o = Gtk.Accessible.AccessibleResetStateMethodInfo
    ResolveFixedMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveFixedMethod "shouldLayout" o = Gtk.Widget.WidgetShouldLayoutMethodInfo
    ResolveFixedMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveFixedMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveFixedMethod "snapshotChild" o = Gtk.Widget.WidgetSnapshotChildMethodInfo
    ResolveFixedMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveFixedMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveFixedMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveFixedMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveFixedMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveFixedMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveFixedMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveFixedMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveFixedMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveFixedMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveFixedMethod "updateNextAccessibleSibling" o = Gtk.Accessible.AccessibleUpdateNextAccessibleSiblingMethodInfo
    ResolveFixedMethod "updateProperty" o = Gtk.Accessible.AccessibleUpdatePropertyMethodInfo
    ResolveFixedMethod "updateRelation" o = Gtk.Accessible.AccessibleUpdateRelationMethodInfo
    ResolveFixedMethod "updateState" o = Gtk.Accessible.AccessibleUpdateStateMethodInfo
    ResolveFixedMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveFixedMethod "getAccessibleParent" o = Gtk.Accessible.AccessibleGetAccessibleParentMethodInfo
    ResolveFixedMethod "getAccessibleRole" o = Gtk.Accessible.AccessibleGetAccessibleRoleMethodInfo
    ResolveFixedMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveFixedMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveFixedMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveFixedMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveFixedMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveFixedMethod "getAtContext" o = Gtk.Accessible.AccessibleGetAtContextMethodInfo
    ResolveFixedMethod "getBounds" o = Gtk.Accessible.AccessibleGetBoundsMethodInfo
    ResolveFixedMethod "getBuildableId" o = Gtk.Buildable.BuildableGetBuildableIdMethodInfo
    ResolveFixedMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveFixedMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveFixedMethod "getChildPosition" o = FixedGetChildPositionMethodInfo
    ResolveFixedMethod "getChildTransform" o = FixedGetChildTransformMethodInfo
    ResolveFixedMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveFixedMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveFixedMethod "getColor" o = Gtk.Widget.WidgetGetColorMethodInfo
    ResolveFixedMethod "getCssClasses" o = Gtk.Widget.WidgetGetCssClassesMethodInfo
    ResolveFixedMethod "getCssName" o = Gtk.Widget.WidgetGetCssNameMethodInfo
    ResolveFixedMethod "getCursor" o = Gtk.Widget.WidgetGetCursorMethodInfo
    ResolveFixedMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveFixedMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveFixedMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveFixedMethod "getFirstAccessibleChild" o = Gtk.Accessible.AccessibleGetFirstAccessibleChildMethodInfo
    ResolveFixedMethod "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveFixedMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    ResolveFixedMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveFixedMethod "getFocusable" o = Gtk.Widget.WidgetGetFocusableMethodInfo
    ResolveFixedMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveFixedMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveFixedMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveFixedMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveFixedMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveFixedMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveFixedMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveFixedMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveFixedMethod "getLastChild" o = Gtk.Widget.WidgetGetLastChildMethodInfo
    ResolveFixedMethod "getLayoutManager" o = Gtk.Widget.WidgetGetLayoutManagerMethodInfo
    ResolveFixedMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveFixedMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveFixedMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveFixedMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveFixedMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveFixedMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveFixedMethod "getNative" o = Gtk.Widget.WidgetGetNativeMethodInfo
    ResolveFixedMethod "getNextAccessibleSibling" o = Gtk.Accessible.AccessibleGetNextAccessibleSiblingMethodInfo
    ResolveFixedMethod "getNextSibling" o = Gtk.Widget.WidgetGetNextSiblingMethodInfo
    ResolveFixedMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveFixedMethod "getOverflow" o = Gtk.Widget.WidgetGetOverflowMethodInfo
    ResolveFixedMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveFixedMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveFixedMethod "getPlatformState" o = Gtk.Accessible.AccessibleGetPlatformStateMethodInfo
    ResolveFixedMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveFixedMethod "getPrevSibling" o = Gtk.Widget.WidgetGetPrevSiblingMethodInfo
    ResolveFixedMethod "getPrimaryClipboard" o = Gtk.Widget.WidgetGetPrimaryClipboardMethodInfo
    ResolveFixedMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveFixedMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveFixedMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveFixedMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveFixedMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveFixedMethod "getRoot" o = Gtk.Widget.WidgetGetRootMethodInfo
    ResolveFixedMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveFixedMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveFixedMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveFixedMethod "getSize" o = Gtk.Widget.WidgetGetSizeMethodInfo
    ResolveFixedMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveFixedMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveFixedMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveFixedMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveFixedMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveFixedMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveFixedMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveFixedMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveFixedMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveFixedMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveFixedMethod "getWidth" o = Gtk.Widget.WidgetGetWidthMethodInfo
    ResolveFixedMethod "setAccessibleParent" o = Gtk.Accessible.AccessibleSetAccessibleParentMethodInfo
    ResolveFixedMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveFixedMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveFixedMethod "setChildTransform" o = FixedSetChildTransformMethodInfo
    ResolveFixedMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveFixedMethod "setCssClasses" o = Gtk.Widget.WidgetSetCssClassesMethodInfo
    ResolveFixedMethod "setCursor" o = Gtk.Widget.WidgetSetCursorMethodInfo
    ResolveFixedMethod "setCursorFromName" o = Gtk.Widget.WidgetSetCursorFromNameMethodInfo
    ResolveFixedMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveFixedMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveFixedMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveFixedMethod "setFocusChild" o = Gtk.Widget.WidgetSetFocusChildMethodInfo
    ResolveFixedMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveFixedMethod "setFocusable" o = Gtk.Widget.WidgetSetFocusableMethodInfo
    ResolveFixedMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveFixedMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveFixedMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveFixedMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveFixedMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveFixedMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveFixedMethod "setLayoutManager" o = Gtk.Widget.WidgetSetLayoutManagerMethodInfo
    ResolveFixedMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveFixedMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveFixedMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveFixedMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveFixedMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveFixedMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveFixedMethod "setOverflow" o = Gtk.Widget.WidgetSetOverflowMethodInfo
    ResolveFixedMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveFixedMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveFixedMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveFixedMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveFixedMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveFixedMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveFixedMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveFixedMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveFixedMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveFixedMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveFixedMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveFixedMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveFixedMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveFixedMethod t Fixed, O.OverloadedMethod info Fixed p) => OL.IsLabel t (Fixed -> 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 ~ ResolveFixedMethod t Fixed, O.OverloadedMethod info Fixed p, R.HasField t Fixed p) => R.HasField t Fixed p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveFixedMethod t Fixed, O.OverloadedMethodInfo info Fixed) => OL.IsLabel t (O.MethodProxy info Fixed) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Fixed
type instance O.AttributeList Fixed = FixedAttributeList
type FixedAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusable", Gtk.Widget.WidgetFocusablePropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Fixed = FixedSignalList
type FixedSignalList = ('[ '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method Fixed::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Fixed" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_fixed_new" gtk_fixed_new :: 
    IO (Ptr Fixed)

-- | Creates a new @GtkFixed@.
fixedNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Fixed
    -- ^ __Returns:__ a new @GtkFixed@.
fixedNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Fixed
fixedNew  = IO Fixed -> m Fixed
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Fixed -> m Fixed) -> IO Fixed -> m Fixed
forall a b. (a -> b) -> a -> b
$ do
    Ptr Fixed
result <- IO (Ptr Fixed)
gtk_fixed_new
    Text -> Ptr Fixed -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fixedNew" Ptr Fixed
result
    Fixed
result' <- ((ManagedPtr Fixed -> Fixed) -> Ptr Fixed -> IO Fixed
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Fixed -> Fixed
Fixed) Ptr Fixed
result
    Fixed -> IO Fixed
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Fixed
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Fixed::get_child_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "fixed"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Fixed" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkFixed`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "widget"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a child of @fixed" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TDouble
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the horizontal position of the @widget"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TDouble
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the vertical position of the @widget"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_fixed_get_child_position" gtk_fixed_get_child_position :: 
    Ptr Fixed ->                            -- fixed : TInterface (Name {namespace = "Gtk", name = "Fixed"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    Ptr CDouble ->                          -- x : TBasicType TDouble
    Ptr CDouble ->                          -- y : TBasicType TDouble
    IO ()

-- | Retrieves the translation transformation of the
-- given child @GtkWidget@ in the @GtkFixed@.
-- 
-- See also: 'GI.Gtk.Objects.Fixed.fixedGetChildTransform'.
fixedGetChildPosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsFixed a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@fixed@/: a @GtkFixed@
    -> b
    -- ^ /@widget@/: a child of /@fixed@/
    -> m ((Double, Double))
fixedGetChildPosition :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsFixed a, IsWidget b) =>
a -> b -> m (Double, Double)
fixedGetChildPosition a
fixed b
widget = IO (Double, Double) -> m (Double, Double)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Double, Double) -> m (Double, Double))
-> IO (Double, Double) -> m (Double, Double)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Fixed
fixed' <- a -> IO (Ptr Fixed)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fixed
    Ptr Widget
widget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
widget
    Ptr CDouble
x <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr CDouble
y <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr Fixed -> Ptr Widget -> Ptr CDouble -> Ptr CDouble -> IO ()
gtk_fixed_get_child_position Ptr Fixed
fixed' Ptr Widget
widget' Ptr CDouble
x Ptr CDouble
y
    CDouble
x' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
x
    let x'' :: Double
x'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
x'
    CDouble
y' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
y
    let y'' :: Double
y'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
y'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fixed
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
widget
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
x
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
y
    (Double, Double) -> IO (Double, Double)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Double
x'', Double
y'')

#if defined(ENABLE_OVERLOADING)
data FixedGetChildPositionMethodInfo
instance (signature ~ (b -> m ((Double, Double))), MonadIO m, IsFixed a, Gtk.Widget.IsWidget b) => O.OverloadedMethod FixedGetChildPositionMethodInfo a signature where
    overloadedMethod = fixedGetChildPosition

instance O.OverloadedMethodInfo FixedGetChildPositionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Fixed.fixedGetChildPosition",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Fixed.html#v:fixedGetChildPosition"
        })


#endif

-- method Fixed::get_child_transform
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "fixed"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Fixed" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkFixed`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "widget"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkWidget`, child of @fixed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gsk" , name = "Transform" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_fixed_get_child_transform" gtk_fixed_get_child_transform :: 
    Ptr Fixed ->                            -- fixed : TInterface (Name {namespace = "Gtk", name = "Fixed"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO (Ptr Gsk.Transform.Transform)

-- | Retrieves the transformation for /@widget@/ set using
-- 'GI.Gtk.Objects.Fixed.fixedSetChildTransform'.
fixedGetChildTransform ::
    (B.CallStack.HasCallStack, MonadIO m, IsFixed a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@fixed@/: a @GtkFixed@
    -> b
    -- ^ /@widget@/: a @GtkWidget@, child of /@fixed@/
    -> m (Maybe Gsk.Transform.Transform)
    -- ^ __Returns:__ a @GskTransform@
fixedGetChildTransform :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsFixed a, IsWidget b) =>
a -> b -> m (Maybe Transform)
fixedGetChildTransform a
fixed b
widget = IO (Maybe Transform) -> m (Maybe Transform)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Transform) -> m (Maybe Transform))
-> IO (Maybe Transform) -> m (Maybe Transform)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Fixed
fixed' <- a -> IO (Ptr Fixed)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fixed
    Ptr Widget
widget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
widget
    Ptr Transform
result <- Ptr Fixed -> Ptr Widget -> IO (Ptr Transform)
gtk_fixed_get_child_transform Ptr Fixed
fixed' Ptr Widget
widget'
    Maybe Transform
maybeResult <- Ptr Transform
-> (Ptr Transform -> IO Transform) -> IO (Maybe Transform)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Transform
result ((Ptr Transform -> IO Transform) -> IO (Maybe Transform))
-> (Ptr Transform -> IO Transform) -> IO (Maybe Transform)
forall a b. (a -> b) -> a -> b
$ \Ptr Transform
result' -> do
        Transform
result'' <- ((ManagedPtr Transform -> Transform)
-> Ptr Transform -> IO Transform
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Transform -> Transform
Gsk.Transform.Transform) Ptr Transform
result'
        Transform -> IO Transform
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Transform
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fixed
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
widget
    Maybe Transform -> IO (Maybe Transform)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Transform
maybeResult

#if defined(ENABLE_OVERLOADING)
data FixedGetChildTransformMethodInfo
instance (signature ~ (b -> m (Maybe Gsk.Transform.Transform)), MonadIO m, IsFixed a, Gtk.Widget.IsWidget b) => O.OverloadedMethod FixedGetChildTransformMethodInfo a signature where
    overloadedMethod = fixedGetChildTransform

instance O.OverloadedMethodInfo FixedGetChildTransformMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Fixed.fixedGetChildTransform",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Fixed.html#v:fixedGetChildTransform"
        })


#endif

-- method Fixed::move
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "fixed"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Fixed" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkFixed`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "widget"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the child widget" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the horizontal position to move the widget to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the vertical position to move the widget to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_fixed_move" gtk_fixed_move :: 
    Ptr Fixed ->                            -- fixed : TInterface (Name {namespace = "Gtk", name = "Fixed"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    CDouble ->                              -- x : TBasicType TDouble
    CDouble ->                              -- y : TBasicType TDouble
    IO ()

-- | Sets a translation transformation to the given /@x@/ and /@y@/
-- coordinates to the child /@widget@/ of the @GtkFixed@.
fixedMove ::
    (B.CallStack.HasCallStack, MonadIO m, IsFixed a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@fixed@/: a @GtkFixed@
    -> b
    -- ^ /@widget@/: the child widget
    -> Double
    -- ^ /@x@/: the horizontal position to move the widget to
    -> Double
    -- ^ /@y@/: the vertical position to move the widget to
    -> m ()
fixedMove :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsFixed a, IsWidget b) =>
a -> b -> Double -> Double -> m ()
fixedMove a
fixed b
widget Double
x Double
y = 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
    Ptr Fixed
fixed' <- a -> IO (Ptr Fixed)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fixed
    Ptr Widget
widget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
widget
    let x' :: CDouble
x' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
x
    let y' :: CDouble
y' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
y
    Ptr Fixed -> Ptr Widget -> CDouble -> CDouble -> IO ()
gtk_fixed_move Ptr Fixed
fixed' Ptr Widget
widget' CDouble
x' CDouble
y'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fixed
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
widget
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FixedMoveMethodInfo
instance (signature ~ (b -> Double -> Double -> m ()), MonadIO m, IsFixed a, Gtk.Widget.IsWidget b) => O.OverloadedMethod FixedMoveMethodInfo a signature where
    overloadedMethod = fixedMove

instance O.OverloadedMethodInfo FixedMoveMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Fixed.fixedMove",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Fixed.html#v:fixedMove"
        })


#endif

-- method Fixed::put
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "fixed"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Fixed" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkFixed`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "widget"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the widget to add" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the horizontal position to place the widget at"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the vertical position to place the widget at"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_fixed_put" gtk_fixed_put :: 
    Ptr Fixed ->                            -- fixed : TInterface (Name {namespace = "Gtk", name = "Fixed"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    CDouble ->                              -- x : TBasicType TDouble
    CDouble ->                              -- y : TBasicType TDouble
    IO ()

-- | Adds a widget to a @GtkFixed@ at the given position.
fixedPut ::
    (B.CallStack.HasCallStack, MonadIO m, IsFixed a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@fixed@/: a @GtkFixed@
    -> b
    -- ^ /@widget@/: the widget to add
    -> Double
    -- ^ /@x@/: the horizontal position to place the widget at
    -> Double
    -- ^ /@y@/: the vertical position to place the widget at
    -> m ()
fixedPut :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsFixed a, IsWidget b) =>
a -> b -> Double -> Double -> m ()
fixedPut a
fixed b
widget Double
x Double
y = 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
    Ptr Fixed
fixed' <- a -> IO (Ptr Fixed)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fixed
    Ptr Widget
widget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
widget
    let x' :: CDouble
x' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
x
    let y' :: CDouble
y' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
y
    Ptr Fixed -> Ptr Widget -> CDouble -> CDouble -> IO ()
gtk_fixed_put Ptr Fixed
fixed' Ptr Widget
widget' CDouble
x' CDouble
y'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fixed
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
widget
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FixedPutMethodInfo
instance (signature ~ (b -> Double -> Double -> m ()), MonadIO m, IsFixed a, Gtk.Widget.IsWidget b) => O.OverloadedMethod FixedPutMethodInfo a signature where
    overloadedMethod = fixedPut

instance O.OverloadedMethodInfo FixedPutMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Fixed.fixedPut",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Fixed.html#v:fixedPut"
        })


#endif

-- method Fixed::remove
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "fixed"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Fixed" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkFixed`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "widget"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the child widget to remove"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_fixed_remove" gtk_fixed_remove :: 
    Ptr Fixed ->                            -- fixed : TInterface (Name {namespace = "Gtk", name = "Fixed"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Removes a child from /@fixed@/.
fixedRemove ::
    (B.CallStack.HasCallStack, MonadIO m, IsFixed a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@fixed@/: a @GtkFixed@
    -> b
    -- ^ /@widget@/: the child widget to remove
    -> m ()
fixedRemove :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsFixed a, IsWidget b) =>
a -> b -> m ()
fixedRemove a
fixed b
widget = 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
    Ptr Fixed
fixed' <- a -> IO (Ptr Fixed)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fixed
    Ptr Widget
widget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
widget
    Ptr Fixed -> Ptr Widget -> IO ()
gtk_fixed_remove Ptr Fixed
fixed' Ptr Widget
widget'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fixed
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
widget
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FixedRemoveMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsFixed a, Gtk.Widget.IsWidget b) => O.OverloadedMethod FixedRemoveMethodInfo a signature where
    overloadedMethod = fixedRemove

instance O.OverloadedMethodInfo FixedRemoveMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Fixed.fixedRemove",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Fixed.html#v:fixedRemove"
        })


#endif

-- method Fixed::set_child_transform
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "fixed"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Fixed" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkFixed`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "widget"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkWidget`, child of @fixed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "transform"
--           , argType =
--               TInterface Name { namespace = "Gsk" , name = "Transform" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the transformation assigned to @widget\n  to reset @widget's transform"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_fixed_set_child_transform" gtk_fixed_set_child_transform :: 
    Ptr Fixed ->                            -- fixed : TInterface (Name {namespace = "Gtk", name = "Fixed"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    Ptr Gsk.Transform.Transform ->          -- transform : TInterface (Name {namespace = "Gsk", name = "Transform"})
    IO ()

-- | Sets the transformation for /@widget@/.
-- 
-- This is a convenience function that retrieves the
-- t'GI.Gtk.Objects.FixedLayoutChild.FixedLayoutChild' instance associated to
-- /@widget@/ and calls 'GI.Gtk.Objects.FixedLayoutChild.fixedLayoutChildSetTransform'.
fixedSetChildTransform ::
    (B.CallStack.HasCallStack, MonadIO m, IsFixed a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@fixed@/: a @GtkFixed@
    -> b
    -- ^ /@widget@/: a @GtkWidget@, child of /@fixed@/
    -> Maybe (Gsk.Transform.Transform)
    -- ^ /@transform@/: the transformation assigned to /@widget@/
    --   to reset /@widget@/\'s transform
    -> m ()
fixedSetChildTransform :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsFixed a, IsWidget b) =>
a -> b -> Maybe Transform -> m ()
fixedSetChildTransform a
fixed b
widget Maybe Transform
transform = 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
    Ptr Fixed
fixed' <- a -> IO (Ptr Fixed)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fixed
    Ptr Widget
widget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
widget
    Ptr Transform
maybeTransform <- case Maybe Transform
transform of
        Maybe Transform
Nothing -> Ptr Transform -> IO (Ptr Transform)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Transform
forall a. Ptr a
nullPtr
        Just Transform
jTransform -> do
            Ptr Transform
jTransform' <- Transform -> IO (Ptr Transform)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Transform
jTransform
            Ptr Transform -> IO (Ptr Transform)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Transform
jTransform'
    Ptr Fixed -> Ptr Widget -> Ptr Transform -> IO ()
gtk_fixed_set_child_transform Ptr Fixed
fixed' Ptr Widget
widget' Ptr Transform
maybeTransform
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fixed
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
widget
    Maybe Transform -> (Transform -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Transform
transform Transform -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FixedSetChildTransformMethodInfo
instance (signature ~ (b -> Maybe (Gsk.Transform.Transform) -> m ()), MonadIO m, IsFixed a, Gtk.Widget.IsWidget b) => O.OverloadedMethod FixedSetChildTransformMethodInfo a signature where
    overloadedMethod = fixedSetChildTransform

instance O.OverloadedMethodInfo FixedSetChildTransformMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Fixed.fixedSetChildTransform",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Fixed.html#v:fixedSetChildTransform"
        })


#endif