{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GtkBinLayout@ is a @GtkLayoutManager@ subclass useful for create \"bins\" of
-- widgets.
-- 
-- @GtkBinLayout@ will stack each child of a widget on top of each other,
-- using the [Widget:hexpand]("GI.Gtk.Objects.Widget#g:attr:hexpand"), [Widget:vexpand]("GI.Gtk.Objects.Widget#g:attr:vexpand"),
-- [Widget:halign]("GI.Gtk.Objects.Widget#g:attr:halign"), and [Widget:valign]("GI.Gtk.Objects.Widget#g:attr:valign") properties
-- of each child to determine where they should be positioned.

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

module GI.Gtk.Objects.BinLayout
    ( 

-- * Exported types
    BinLayout(..)                           ,
    IsBinLayout                             ,
    toBinLayout                             ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [allocate]("GI.Gtk.Objects.LayoutManager#g:method:allocate"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [layoutChanged]("GI.Gtk.Objects.LayoutManager#g:method:layoutChanged"), [measure]("GI.Gtk.Objects.LayoutManager#g:method:measure"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getLayoutChild]("GI.Gtk.Objects.LayoutManager#g:method:getLayoutChild"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRequestMode]("GI.Gtk.Objects.LayoutManager#g:method:getRequestMode"), [getWidget]("GI.Gtk.Objects.LayoutManager#g:method:getWidget").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveBinLayoutMethod                  ,
#endif

-- ** new #method:new#

    binLayoutNew                            ,




    ) 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 {-# SOURCE #-} qualified GI.Gtk.Objects.LayoutManager as Gtk.LayoutManager

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

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

foreign import ccall "gtk_bin_layout_get_type"
    c_gtk_bin_layout_get_type :: IO B.Types.GType

instance B.Types.TypedObject BinLayout where
    glibType :: IO GType
glibType = IO GType
c_gtk_bin_layout_get_type

instance B.Types.GObject BinLayout

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

instance O.HasParentTypes BinLayout
type instance O.ParentTypes BinLayout = '[Gtk.LayoutManager.LayoutManager, GObject.Object.Object]

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

-- | Convert 'BinLayout' 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 BinLayout) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_bin_layout_get_type
    gvalueSet_ :: Ptr GValue -> Maybe BinLayout -> IO ()
gvalueSet_ Ptr GValue
gv Maybe BinLayout
P.Nothing = Ptr GValue -> Ptr BinLayout -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr BinLayout
forall a. Ptr a
FP.nullPtr :: FP.Ptr BinLayout)
    gvalueSet_ Ptr GValue
gv (P.Just BinLayout
obj) = BinLayout -> (Ptr BinLayout -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr BinLayout
obj (Ptr GValue -> Ptr BinLayout -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe BinLayout)
gvalueGet_ Ptr GValue
gv = do
        Ptr BinLayout
ptr <- Ptr GValue -> IO (Ptr BinLayout)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr BinLayout)
        if Ptr BinLayout
ptr Ptr BinLayout -> Ptr BinLayout -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr BinLayout
forall a. Ptr a
FP.nullPtr
        then BinLayout -> Maybe BinLayout
forall a. a -> Maybe a
P.Just (BinLayout -> Maybe BinLayout)
-> IO BinLayout -> IO (Maybe BinLayout)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr BinLayout -> BinLayout)
-> Ptr BinLayout -> IO BinLayout
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr BinLayout -> BinLayout
BinLayout Ptr BinLayout
ptr
        else Maybe BinLayout -> IO (Maybe BinLayout)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe BinLayout
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveBinLayoutMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveBinLayoutMethod "allocate" o = Gtk.LayoutManager.LayoutManagerAllocateMethodInfo
    ResolveBinLayoutMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveBinLayoutMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveBinLayoutMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveBinLayoutMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveBinLayoutMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveBinLayoutMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveBinLayoutMethod "layoutChanged" o = Gtk.LayoutManager.LayoutManagerLayoutChangedMethodInfo
    ResolveBinLayoutMethod "measure" o = Gtk.LayoutManager.LayoutManagerMeasureMethodInfo
    ResolveBinLayoutMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveBinLayoutMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveBinLayoutMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveBinLayoutMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveBinLayoutMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveBinLayoutMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveBinLayoutMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveBinLayoutMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveBinLayoutMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveBinLayoutMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveBinLayoutMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveBinLayoutMethod "getLayoutChild" o = Gtk.LayoutManager.LayoutManagerGetLayoutChildMethodInfo
    ResolveBinLayoutMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveBinLayoutMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveBinLayoutMethod "getRequestMode" o = Gtk.LayoutManager.LayoutManagerGetRequestModeMethodInfo
    ResolveBinLayoutMethod "getWidget" o = Gtk.LayoutManager.LayoutManagerGetWidgetMethodInfo
    ResolveBinLayoutMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveBinLayoutMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveBinLayoutMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveBinLayoutMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList BinLayout
type instance O.AttributeList BinLayout = BinLayoutAttributeList
type BinLayoutAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList BinLayout = BinLayoutSignalList
type BinLayoutSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

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

foreign import ccall "gtk_bin_layout_new" gtk_bin_layout_new :: 
    IO (Ptr BinLayout)

-- | Creates a new @GtkBinLayout@ instance.
binLayoutNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m BinLayout
    -- ^ __Returns:__ the newly created @GtkBinLayout@
binLayoutNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m BinLayout
binLayoutNew  = IO BinLayout -> m BinLayout
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BinLayout -> m BinLayout) -> IO BinLayout -> m BinLayout
forall a b. (a -> b) -> a -> b
$ do
    Ptr BinLayout
result <- IO (Ptr BinLayout)
gtk_bin_layout_new
    Text -> Ptr BinLayout -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"binLayoutNew" Ptr BinLayout
result
    BinLayout
result' <- ((ManagedPtr BinLayout -> BinLayout)
-> Ptr BinLayout -> IO BinLayout
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr BinLayout -> BinLayout
BinLayout) Ptr BinLayout
result
    BinLayout -> IO BinLayout
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return BinLayout
result'

#if defined(ENABLE_OVERLOADING)
#endif