{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A @GdkContentFormatsBuilder@ is an auxiliary struct used to create
-- new @GdkContentFormats@, and should not be kept around.

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

module GI.Gdk.Structs.ContentFormatsBuilder
    ( 

-- * Exported types
    ContentFormatsBuilder(..)               ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addFormats]("GI.Gdk.Structs.ContentFormatsBuilder#g:method:addFormats"), [addGtype]("GI.Gdk.Structs.ContentFormatsBuilder#g:method:addGtype"), [addMimeType]("GI.Gdk.Structs.ContentFormatsBuilder#g:method:addMimeType"), [ref]("GI.Gdk.Structs.ContentFormatsBuilder#g:method:ref"), [toFormats]("GI.Gdk.Structs.ContentFormatsBuilder#g:method:toFormats"), [unref]("GI.Gdk.Structs.ContentFormatsBuilder#g:method:unref").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveContentFormatsBuilderMethod      ,
#endif

-- ** addFormats #method:addFormats#

#if defined(ENABLE_OVERLOADING)
    ContentFormatsBuilderAddFormatsMethodInfo,
#endif
    contentFormatsBuilderAddFormats         ,


-- ** addGtype #method:addGtype#

#if defined(ENABLE_OVERLOADING)
    ContentFormatsBuilderAddGtypeMethodInfo ,
#endif
    contentFormatsBuilderAddGtype           ,


-- ** addMimeType #method:addMimeType#

#if defined(ENABLE_OVERLOADING)
    ContentFormatsBuilderAddMimeTypeMethodInfo,
#endif
    contentFormatsBuilderAddMimeType        ,


-- ** new #method:new#

    contentFormatsBuilderNew                ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    ContentFormatsBuilderRefMethodInfo      ,
#endif
    contentFormatsBuilderRef                ,


-- ** toFormats #method:toFormats#

#if defined(ENABLE_OVERLOADING)
    ContentFormatsBuilderToFormatsMethodInfo,
#endif
    contentFormatsBuilderToFormats          ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    ContentFormatsBuilderUnrefMethodInfo    ,
#endif
    contentFormatsBuilderUnref              ,




    ) 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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Structs.String as GLib.String
import {-# SOURCE #-} qualified GI.Gdk.Structs.ContentFormats as Gdk.ContentFormats

#else
import {-# SOURCE #-} qualified GI.Gdk.Structs.ContentFormats as Gdk.ContentFormats

#endif

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

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

foreign import ccall "gdk_content_formats_builder_get_type" c_gdk_content_formats_builder_get_type :: 
    IO GType

type instance O.ParentTypes ContentFormatsBuilder = '[]
instance O.HasParentTypes ContentFormatsBuilder

instance B.Types.TypedObject ContentFormatsBuilder where
    glibType :: IO GType
glibType = IO GType
c_gdk_content_formats_builder_get_type

instance B.Types.GBoxed ContentFormatsBuilder

-- | Convert 'ContentFormatsBuilder' 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 ContentFormatsBuilder) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_content_formats_builder_get_type
    gvalueSet_ :: Ptr GValue -> Maybe ContentFormatsBuilder -> IO ()
gvalueSet_ Ptr GValue
gv Maybe ContentFormatsBuilder
P.Nothing = Ptr GValue -> Ptr ContentFormatsBuilder -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr ContentFormatsBuilder
forall a. Ptr a
FP.nullPtr :: FP.Ptr ContentFormatsBuilder)
    gvalueSet_ Ptr GValue
gv (P.Just ContentFormatsBuilder
obj) = ContentFormatsBuilder
-> (Ptr ContentFormatsBuilder -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ContentFormatsBuilder
obj (Ptr GValue -> Ptr ContentFormatsBuilder -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe ContentFormatsBuilder)
gvalueGet_ Ptr GValue
gv = do
        ptr <- Ptr GValue -> IO (Ptr ContentFormatsBuilder)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr ContentFormatsBuilder)
        if ptr /= FP.nullPtr
        then P.Just <$> B.ManagedPtr.newBoxed ContentFormatsBuilder ptr
        else return P.Nothing
        
    


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

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

foreign import ccall "gdk_content_formats_builder_new" gdk_content_formats_builder_new :: 
    IO (Ptr ContentFormatsBuilder)

-- | Create a new @GdkContentFormatsBuilder@ object.
-- 
-- The resulting builder would create an empty @GdkContentFormats@.
-- Use addition functions to add types to it.
contentFormatsBuilderNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m ContentFormatsBuilder
    -- ^ __Returns:__ a new @GdkContentFormatsBuilder@
contentFormatsBuilderNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
m ContentFormatsBuilder
contentFormatsBuilderNew  = IO ContentFormatsBuilder -> m ContentFormatsBuilder
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ContentFormatsBuilder -> m ContentFormatsBuilder)
-> IO ContentFormatsBuilder -> m ContentFormatsBuilder
forall a b. (a -> b) -> a -> b
$ do
    result <- IO (Ptr ContentFormatsBuilder)
gdk_content_formats_builder_new
    checkUnexpectedReturnNULL "contentFormatsBuilderNew" result
    result' <- (wrapBoxed ContentFormatsBuilder) result
    return result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method ContentFormatsBuilder::add_formats
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "builder"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "ContentFormatsBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkContentFormatsBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "formats"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ContentFormats" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the formats to add" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_content_formats_builder_add_formats" gdk_content_formats_builder_add_formats :: 
    Ptr ContentFormatsBuilder ->            -- builder : TInterface (Name {namespace = "Gdk", name = "ContentFormatsBuilder"})
    Ptr Gdk.ContentFormats.ContentFormats -> -- formats : TInterface (Name {namespace = "Gdk", name = "ContentFormats"})
    IO ()

-- | Appends all formats from /@formats@/ to /@builder@/, skipping those that
-- already exist.
contentFormatsBuilderAddFormats ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ContentFormatsBuilder
    -- ^ /@builder@/: a @GdkContentFormatsBuilder@
    -> Gdk.ContentFormats.ContentFormats
    -- ^ /@formats@/: the formats to add
    -> m ()
contentFormatsBuilderAddFormats :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ContentFormatsBuilder -> ContentFormats -> m ()
contentFormatsBuilderAddFormats ContentFormatsBuilder
builder ContentFormats
formats = 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
    builder' <- ContentFormatsBuilder -> IO (Ptr ContentFormatsBuilder)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ContentFormatsBuilder
builder
    formats' <- unsafeManagedPtrGetPtr formats
    gdk_content_formats_builder_add_formats builder' formats'
    touchManagedPtr builder
    touchManagedPtr formats
    return ()

#if defined(ENABLE_OVERLOADING)
data ContentFormatsBuilderAddFormatsMethodInfo
instance (signature ~ (Gdk.ContentFormats.ContentFormats -> m ()), MonadIO m) => O.OverloadedMethod ContentFormatsBuilderAddFormatsMethodInfo ContentFormatsBuilder signature where
    overloadedMethod = contentFormatsBuilderAddFormats

instance O.OverloadedMethodInfo ContentFormatsBuilderAddFormatsMethodInfo ContentFormatsBuilder where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.ContentFormatsBuilder.contentFormatsBuilderAddFormats",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Structs-ContentFormatsBuilder.html#v:contentFormatsBuilderAddFormats"
        })


#endif

-- method ContentFormatsBuilder::add_gtype
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "builder"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "ContentFormatsBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkContentFormats`Builder"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType = TBasicType TGType
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GType`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_content_formats_builder_add_gtype" gdk_content_formats_builder_add_gtype :: 
    Ptr ContentFormatsBuilder ->            -- builder : TInterface (Name {namespace = "Gdk", name = "ContentFormatsBuilder"})
    CGType ->                               -- type : TBasicType TGType
    IO ()

-- | Appends /@type@/ to /@builder@/ if it has not already been added.
contentFormatsBuilderAddGtype ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ContentFormatsBuilder
    -- ^ /@builder@/: a @GdkContentFormats@Builder
    -> GType
    -- ^ /@type@/: a @GType@
    -> m ()
contentFormatsBuilderAddGtype :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ContentFormatsBuilder -> GType -> m ()
contentFormatsBuilderAddGtype ContentFormatsBuilder
builder GType
type_ = 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
    builder' <- ContentFormatsBuilder -> IO (Ptr ContentFormatsBuilder)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ContentFormatsBuilder
builder
    let type_' = GType -> CGType
gtypeToCGType GType
type_
    gdk_content_formats_builder_add_gtype builder' type_'
    touchManagedPtr builder
    return ()

#if defined(ENABLE_OVERLOADING)
data ContentFormatsBuilderAddGtypeMethodInfo
instance (signature ~ (GType -> m ()), MonadIO m) => O.OverloadedMethod ContentFormatsBuilderAddGtypeMethodInfo ContentFormatsBuilder signature where
    overloadedMethod = contentFormatsBuilderAddGtype

instance O.OverloadedMethodInfo ContentFormatsBuilderAddGtypeMethodInfo ContentFormatsBuilder where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.ContentFormatsBuilder.contentFormatsBuilderAddGtype",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Structs-ContentFormatsBuilder.html#v:contentFormatsBuilderAddGtype"
        })


#endif

-- method ContentFormatsBuilder::add_mime_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "builder"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "ContentFormatsBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkContentFormatsBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mime_type"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a mime type" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_content_formats_builder_add_mime_type" gdk_content_formats_builder_add_mime_type :: 
    Ptr ContentFormatsBuilder ->            -- builder : TInterface (Name {namespace = "Gdk", name = "ContentFormatsBuilder"})
    CString ->                              -- mime_type : TBasicType TUTF8
    IO ()

-- | Appends /@mimeType@/ to /@builder@/ if it has not already been added.
contentFormatsBuilderAddMimeType ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ContentFormatsBuilder
    -- ^ /@builder@/: a @GdkContentFormatsBuilder@
    -> T.Text
    -- ^ /@mimeType@/: a mime type
    -> m ()
contentFormatsBuilderAddMimeType :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ContentFormatsBuilder -> Text -> m ()
contentFormatsBuilderAddMimeType ContentFormatsBuilder
builder Text
mimeType = 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
    builder' <- ContentFormatsBuilder -> IO (Ptr ContentFormatsBuilder)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ContentFormatsBuilder
builder
    mimeType' <- textToCString mimeType
    gdk_content_formats_builder_add_mime_type builder' mimeType'
    touchManagedPtr builder
    freeMem mimeType'
    return ()

#if defined(ENABLE_OVERLOADING)
data ContentFormatsBuilderAddMimeTypeMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m) => O.OverloadedMethod ContentFormatsBuilderAddMimeTypeMethodInfo ContentFormatsBuilder signature where
    overloadedMethod = contentFormatsBuilderAddMimeType

instance O.OverloadedMethodInfo ContentFormatsBuilderAddMimeTypeMethodInfo ContentFormatsBuilder where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.ContentFormatsBuilder.contentFormatsBuilderAddMimeType",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Structs-ContentFormatsBuilder.html#v:contentFormatsBuilderAddMimeType"
        })


#endif

-- method ContentFormatsBuilder::ref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "builder"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "ContentFormatsBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkContentFormatsBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gdk" , name = "ContentFormatsBuilder" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_content_formats_builder_ref" gdk_content_formats_builder_ref :: 
    Ptr ContentFormatsBuilder ->            -- builder : TInterface (Name {namespace = "Gdk", name = "ContentFormatsBuilder"})
    IO (Ptr ContentFormatsBuilder)

-- | Acquires a reference on the given /@builder@/.
-- 
-- This function is intended primarily for bindings.
-- @GdkContentFormatsBuilder@ objects should not be kept around.
contentFormatsBuilderRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ContentFormatsBuilder
    -- ^ /@builder@/: a @GdkContentFormatsBuilder@
    -> m ContentFormatsBuilder
    -- ^ __Returns:__ the given @GdkContentFormatsBuilder@
    --   with its reference count increased
contentFormatsBuilderRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ContentFormatsBuilder -> m ContentFormatsBuilder
contentFormatsBuilderRef ContentFormatsBuilder
builder = IO ContentFormatsBuilder -> m ContentFormatsBuilder
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ContentFormatsBuilder -> m ContentFormatsBuilder)
-> IO ContentFormatsBuilder -> m ContentFormatsBuilder
forall a b. (a -> b) -> a -> b
$ do
    builder' <- ContentFormatsBuilder -> IO (Ptr ContentFormatsBuilder)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ContentFormatsBuilder
builder
    result <- gdk_content_formats_builder_ref builder'
    checkUnexpectedReturnNULL "contentFormatsBuilderRef" result
    result' <- (newBoxed ContentFormatsBuilder) result
    touchManagedPtr builder
    return result'

#if defined(ENABLE_OVERLOADING)
data ContentFormatsBuilderRefMethodInfo
instance (signature ~ (m ContentFormatsBuilder), MonadIO m) => O.OverloadedMethod ContentFormatsBuilderRefMethodInfo ContentFormatsBuilder signature where
    overloadedMethod = contentFormatsBuilderRef

instance O.OverloadedMethodInfo ContentFormatsBuilderRefMethodInfo ContentFormatsBuilder where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.ContentFormatsBuilder.contentFormatsBuilderRef",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Structs-ContentFormatsBuilder.html#v:contentFormatsBuilderRef"
        })


#endif

-- method ContentFormatsBuilder::to_formats
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "builder"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "ContentFormatsBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkContentFormats`Builder"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gdk" , name = "ContentFormats" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_content_formats_builder_to_formats" gdk_content_formats_builder_to_formats :: 
    Ptr ContentFormatsBuilder ->            -- builder : TInterface (Name {namespace = "Gdk", name = "ContentFormatsBuilder"})
    IO (Ptr Gdk.ContentFormats.ContentFormats)

-- | Creates a new @GdkContentFormats@ from the given /@builder@/.
-- 
-- The given @GdkContentFormatsBuilder@ is reset once this function returns;
-- you cannot call this function multiple times on the same /@builder@/ instance.
-- 
-- This function is intended primarily for bindings. C code should use
-- t'GI.Gdk.Structs.ContentFormatsBuilder.ContentFormatsBuilder'.@/free_to_formats/@().
contentFormatsBuilderToFormats ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ContentFormatsBuilder
    -- ^ /@builder@/: a @GdkContentFormats@Builder
    -> m Gdk.ContentFormats.ContentFormats
    -- ^ __Returns:__ the newly created @GdkContentFormats@
    --   with all the formats added to /@builder@/
contentFormatsBuilderToFormats :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ContentFormatsBuilder -> m ContentFormats
contentFormatsBuilderToFormats ContentFormatsBuilder
builder = IO ContentFormats -> m ContentFormats
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ContentFormats -> m ContentFormats)
-> IO ContentFormats -> m ContentFormats
forall a b. (a -> b) -> a -> b
$ do
    builder' <- ContentFormatsBuilder -> IO (Ptr ContentFormatsBuilder)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ContentFormatsBuilder
builder
    result <- gdk_content_formats_builder_to_formats builder'
    checkUnexpectedReturnNULL "contentFormatsBuilderToFormats" result
    result' <- (wrapBoxed Gdk.ContentFormats.ContentFormats) result
    touchManagedPtr builder
    return result'

#if defined(ENABLE_OVERLOADING)
data ContentFormatsBuilderToFormatsMethodInfo
instance (signature ~ (m Gdk.ContentFormats.ContentFormats), MonadIO m) => O.OverloadedMethod ContentFormatsBuilderToFormatsMethodInfo ContentFormatsBuilder signature where
    overloadedMethod = contentFormatsBuilderToFormats

instance O.OverloadedMethodInfo ContentFormatsBuilderToFormatsMethodInfo ContentFormatsBuilder where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.ContentFormatsBuilder.contentFormatsBuilderToFormats",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Structs-ContentFormatsBuilder.html#v:contentFormatsBuilderToFormats"
        })


#endif

-- method ContentFormatsBuilder::unref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "builder"
--           , argType =
--               TInterface
--                 Name { namespace = "Gdk" , name = "ContentFormatsBuilder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkContentFormatsBuilder`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_content_formats_builder_unref" gdk_content_formats_builder_unref :: 
    Ptr ContentFormatsBuilder ->            -- builder : TInterface (Name {namespace = "Gdk", name = "ContentFormatsBuilder"})
    IO ()

-- | Releases a reference on the given /@builder@/.
contentFormatsBuilderUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ContentFormatsBuilder
    -- ^ /@builder@/: a @GdkContentFormatsBuilder@
    -> m ()
contentFormatsBuilderUnref :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ContentFormatsBuilder -> m ()
contentFormatsBuilderUnref ContentFormatsBuilder
builder = 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
    builder' <- ContentFormatsBuilder -> IO (Ptr ContentFormatsBuilder)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ContentFormatsBuilder
builder
    gdk_content_formats_builder_unref builder'
    touchManagedPtr builder
    return ()

#if defined(ENABLE_OVERLOADING)
data ContentFormatsBuilderUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod ContentFormatsBuilderUnrefMethodInfo ContentFormatsBuilder signature where
    overloadedMethod = contentFormatsBuilderUnref

instance O.OverloadedMethodInfo ContentFormatsBuilderUnrefMethodInfo ContentFormatsBuilder where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.ContentFormatsBuilder.contentFormatsBuilderUnref",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.9/docs/GI-Gdk-Structs-ContentFormatsBuilder.html#v:contentFormatsBuilderUnref"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveContentFormatsBuilderMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveContentFormatsBuilderMethod "addFormats" o = ContentFormatsBuilderAddFormatsMethodInfo
    ResolveContentFormatsBuilderMethod "addGtype" o = ContentFormatsBuilderAddGtypeMethodInfo
    ResolveContentFormatsBuilderMethod "addMimeType" o = ContentFormatsBuilderAddMimeTypeMethodInfo
    ResolveContentFormatsBuilderMethod "ref" o = ContentFormatsBuilderRefMethodInfo
    ResolveContentFormatsBuilderMethod "toFormats" o = ContentFormatsBuilderToFormatsMethodInfo
    ResolveContentFormatsBuilderMethod "unref" o = ContentFormatsBuilderUnrefMethodInfo
    ResolveContentFormatsBuilderMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif