{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gtk.Objects.ListItemFactory.ListItemFactory' is one of the core concepts of handling list widgets.
-- It is the object tasked with creating widgets for items taken from a
-- t'GI.Gio.Interfaces.ListModel.ListModel' when the views need them and updating them as the items
-- displayed by the view change.
-- 
-- A view is usually only able to display anything after both a factory
-- and a model have been set on the view. So it is important that you do
-- not skip this step when setting up your first view.
-- 
-- Because views do not display the whole list at once but only a few
-- items, they only need to maintain a few widgets at a time. They will
-- instruct the t'GI.Gtk.Objects.ListItemFactory.ListItemFactory' to create these widgets and bind them
-- to the items that are currently displayed.
-- As the list model changes or the user scrolls to the list, the items will
-- change and the view will instruct the factory to bind the widgets to those
-- new items.
-- 
-- The actual widgets used for displaying those widgets is provided by you.
-- 
-- When the factory needs widgets created, it will create a t'GI.Gtk.Objects.ListItem.ListItem' and
-- hand it to your code to set up a widget for. This list item will provide
-- various properties with information about what item to display and provide
-- you with some opportunities to configure its behavior. See the t'GI.Gtk.Objects.ListItem.ListItem'
-- documentation for further details.
-- 
-- Various implementations of t'GI.Gtk.Objects.ListItemFactory.ListItemFactory' exist to allow you different
-- ways to provide those widgets. The most common implementations are
-- t'GI.Gtk.Objects.BuilderListItemFactory.BuilderListItemFactory' which takes a t'GI.Gtk.Objects.Builder.Builder' .ui file and then creates
-- widgets and manages everything automatically from the information in that file
-- and t'GI.Gtk.Objects.SignalListItemFactory.SignalListItemFactory' which allows you to connect to signals with your
-- own code and retain full control over how the widgets are setup and managed.
-- 
-- A t'GI.Gtk.Objects.ListItemFactory.ListItemFactory' is supposed to be final - that means its behavior should
-- not change and the first widget created from it should behave the same way as
-- the last widget created from it.
-- If you intend to do changes to the behavior, it is recommended that you create
-- a new t'GI.Gtk.Objects.ListItemFactory.ListItemFactory' which will allow the views to recreate its widgets.
-- 
-- Once you have chosen your factory and created it, you need to set it on the
-- view widget you want to use it with, such as via 'GI.Gtk.Objects.ListView.listViewSetFactory'.
-- Reusing factories across different views is allowed, but very uncommon.

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

module GI.Gtk.Objects.ListItemFactory
    ( 

-- * Exported types
    ListItemFactory(..)                     ,
    IsListItemFactory                       ,
    toListItemFactory                       ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [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"), [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"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== 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)
    ResolveListItemFactoryMethod            ,
#endif



    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object

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

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

foreign import ccall "gtk_list_item_factory_get_type"
    c_gtk_list_item_factory_get_type :: IO B.Types.GType

instance B.Types.TypedObject ListItemFactory where
    glibType :: IO GType
glibType = IO GType
c_gtk_list_item_factory_get_type

instance B.Types.GObject ListItemFactory

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

instance O.HasParentTypes ListItemFactory
type instance O.ParentTypes ListItemFactory = '[GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveListItemFactoryMethod (t :: Symbol) (o :: *) :: * where
    ResolveListItemFactoryMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveListItemFactoryMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveListItemFactoryMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveListItemFactoryMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveListItemFactoryMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveListItemFactoryMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveListItemFactoryMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveListItemFactoryMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveListItemFactoryMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveListItemFactoryMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveListItemFactoryMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveListItemFactoryMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveListItemFactoryMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveListItemFactoryMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveListItemFactoryMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveListItemFactoryMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveListItemFactoryMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveListItemFactoryMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveListItemFactoryMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveListItemFactoryMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveListItemFactoryMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveListItemFactoryMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveListItemFactoryMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ListItemFactory
type instance O.AttributeList ListItemFactory = ListItemFactoryAttributeList
type ListItemFactoryAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ListItemFactory = ListItemFactorySignalList
type ListItemFactorySignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif