{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.Vips.Objects.Operation
    ( 

-- * Exported types
    Operation(..)                           ,
    IsOperation                             ,
    toOperation                             ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [argumentIsset]("GI.Vips.Objects.Object#g:method:argumentIsset"), [argumentNeedsstring]("GI.Vips.Objects.Object#g:method:argumentNeedsstring"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [build]("GI.Vips.Objects.Object#g:method:build"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [invalidate]("GI.Vips.Objects.Operation#g:method:invalidate"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [localCb]("GI.Vips.Objects.Object#g:method:localCb"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [preclose]("GI.Vips.Objects.Object#g:method:preclose"), [printDump]("GI.Vips.Objects.Object#g:method:printDump"), [printName]("GI.Vips.Objects.Object#g:method:printName"), [printSummary]("GI.Vips.Objects.Object#g:method:printSummary"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [rewind]("GI.Vips.Objects.Object#g:method:rewind"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [sanity]("GI.Vips.Objects.Object#g:method:sanity"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [toString]("GI.Vips.Objects.Object#g:method:toString"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unrefOutputs]("GI.Vips.Objects.Object#g:method:unrefOutputs"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getArgumentFlags]("GI.Vips.Objects.Object#g:method:getArgumentFlags"), [getArgumentPriority]("GI.Vips.Objects.Object#g:method:getArgumentPriority"), [getArgumentToString]("GI.Vips.Objects.Object#g:method:getArgumentToString"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDescription]("GI.Vips.Objects.Object#g:method:getDescription"), [getFlags]("GI.Vips.Objects.Operation#g:method:getFlags"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setArgumentFromString]("GI.Vips.Objects.Object#g:method:setArgumentFromString"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setFromString]("GI.Vips.Objects.Object#g:method:setFromString"), [setRequired]("GI.Vips.Objects.Object#g:method:setRequired"), [setStatic]("GI.Vips.Objects.Object#g:method:setStatic").

#if defined(ENABLE_OVERLOADING)
    ResolveOperationMethod                  ,
#endif

-- ** blockSet #method:blockSet#

    operationBlockSet                       ,


-- ** getFlags #method:getFlags#

#if defined(ENABLE_OVERLOADING)
    OperationGetFlagsMethodInfo             ,
#endif
    operationGetFlags                       ,


-- ** invalidate #method:invalidate#

#if defined(ENABLE_OVERLOADING)
    OperationInvalidateMethodInfo           ,
#endif
    operationInvalidate                     ,


-- ** new #method:new#

    operationNew                            ,




 -- * Signals


-- ** invalidate #signal:invalidate#

    OperationInvalidateCallback             ,
#if defined(ENABLE_OVERLOADING)
    OperationInvalidateSignalInfo           ,
#endif
    afterOperationInvalidate                ,
    onOperationInvalidate                   ,




    ) 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.Vips.Flags as Vips.Flags
import {-# SOURCE #-} qualified GI.Vips.Objects.Object as Vips.Object

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

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

foreign import ccall "vips_operation_get_type"
    c_vips_operation_get_type :: IO B.Types.GType

instance B.Types.TypedObject Operation where
    glibType :: IO GType
glibType = IO GType
c_vips_operation_get_type

instance B.Types.GObject Operation

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

instance O.HasParentTypes Operation
type instance O.ParentTypes Operation = '[Vips.Object.Object, GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveOperationMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveOperationMethod "argumentIsset" o = Vips.Object.ObjectArgumentIssetMethodInfo
    ResolveOperationMethod "argumentNeedsstring" o = Vips.Object.ObjectArgumentNeedsstringMethodInfo
    ResolveOperationMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveOperationMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveOperationMethod "build" o = Vips.Object.ObjectBuildMethodInfo
    ResolveOperationMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveOperationMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveOperationMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveOperationMethod "invalidate" o = OperationInvalidateMethodInfo
    ResolveOperationMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveOperationMethod "localCb" o = Vips.Object.ObjectLocalCbMethodInfo
    ResolveOperationMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveOperationMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveOperationMethod "preclose" o = Vips.Object.ObjectPrecloseMethodInfo
    ResolveOperationMethod "printDump" o = Vips.Object.ObjectPrintDumpMethodInfo
    ResolveOperationMethod "printName" o = Vips.Object.ObjectPrintNameMethodInfo
    ResolveOperationMethod "printSummary" o = Vips.Object.ObjectPrintSummaryMethodInfo
    ResolveOperationMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveOperationMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveOperationMethod "rewind" o = Vips.Object.ObjectRewindMethodInfo
    ResolveOperationMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveOperationMethod "sanity" o = Vips.Object.ObjectSanityMethodInfo
    ResolveOperationMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveOperationMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveOperationMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveOperationMethod "toString" o = Vips.Object.ObjectToStringMethodInfo
    ResolveOperationMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveOperationMethod "unrefOutputs" o = Vips.Object.ObjectUnrefOutputsMethodInfo
    ResolveOperationMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveOperationMethod "getArgumentFlags" o = Vips.Object.ObjectGetArgumentFlagsMethodInfo
    ResolveOperationMethod "getArgumentPriority" o = Vips.Object.ObjectGetArgumentPriorityMethodInfo
    ResolveOperationMethod "getArgumentToString" o = Vips.Object.ObjectGetArgumentToStringMethodInfo
    ResolveOperationMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveOperationMethod "getDescription" o = Vips.Object.ObjectGetDescriptionMethodInfo
    ResolveOperationMethod "getFlags" o = OperationGetFlagsMethodInfo
    ResolveOperationMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveOperationMethod "setArgumentFromString" o = Vips.Object.ObjectSetArgumentFromStringMethodInfo
    ResolveOperationMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveOperationMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveOperationMethod "setFromString" o = Vips.Object.ObjectSetFromStringMethodInfo
    ResolveOperationMethod "setRequired" o = Vips.Object.ObjectSetRequiredMethodInfo
    ResolveOperationMethod "setStatic" o = Vips.Object.ObjectSetStaticMethodInfo
    ResolveOperationMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- signal Operation::invalidate
-- | /No description available in the introspection data./
type OperationInvalidateCallback =
    IO ()

type C_OperationInvalidateCallback =
    Ptr Operation ->                        -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_OperationInvalidateCallback`.
foreign import ccall "wrapper"
    mk_OperationInvalidateCallback :: C_OperationInvalidateCallback -> IO (FunPtr C_OperationInvalidateCallback)

wrap_OperationInvalidateCallback :: 
    GObject a => (a -> OperationInvalidateCallback) ->
    C_OperationInvalidateCallback
wrap_OperationInvalidateCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_OperationInvalidateCallback
wrap_OperationInvalidateCallback a -> IO ()
gi'cb Ptr Operation
gi'selfPtr Ptr ()
_ = do
    Ptr Operation -> (Operation -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Operation
gi'selfPtr ((Operation -> IO ()) -> IO ()) -> (Operation -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Operation
gi'self -> a -> IO ()
gi'cb (Operation -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Operation
gi'self) 


-- | Connect a signal handler for the [invalidate](#signal:invalidate) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' operation #invalidate callback
-- @
-- 
-- 
onOperationInvalidate :: (IsOperation a, MonadIO m) => a -> ((?self :: a) => OperationInvalidateCallback) -> m SignalHandlerId
onOperationInvalidate :: forall a (m :: * -> *).
(IsOperation a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onOperationInvalidate a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_OperationInvalidateCallback
wrapped' = (a -> IO ()) -> C_OperationInvalidateCallback
forall a.
GObject a =>
(a -> IO ()) -> C_OperationInvalidateCallback
wrap_OperationInvalidateCallback a -> IO ()
wrapped
    FunPtr C_OperationInvalidateCallback
wrapped'' <- C_OperationInvalidateCallback
-> IO (FunPtr C_OperationInvalidateCallback)
mk_OperationInvalidateCallback C_OperationInvalidateCallback
wrapped'
    a
-> Text
-> FunPtr C_OperationInvalidateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"invalidate" FunPtr C_OperationInvalidateCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [invalidate](#signal:invalidate) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' operation #invalidate callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterOperationInvalidate :: (IsOperation a, MonadIO m) => a -> ((?self :: a) => OperationInvalidateCallback) -> m SignalHandlerId
afterOperationInvalidate :: forall a (m :: * -> *).
(IsOperation a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterOperationInvalidate a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_OperationInvalidateCallback
wrapped' = (a -> IO ()) -> C_OperationInvalidateCallback
forall a.
GObject a =>
(a -> IO ()) -> C_OperationInvalidateCallback
wrap_OperationInvalidateCallback a -> IO ()
wrapped
    FunPtr C_OperationInvalidateCallback
wrapped'' <- C_OperationInvalidateCallback
-> IO (FunPtr C_OperationInvalidateCallback)
mk_OperationInvalidateCallback C_OperationInvalidateCallback
wrapped'
    a
-> Text
-> FunPtr C_OperationInvalidateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"invalidate" FunPtr C_OperationInvalidateCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data OperationInvalidateSignalInfo
instance SignalInfo OperationInvalidateSignalInfo where
    type HaskellCallbackType OperationInvalidateSignalInfo = OperationInvalidateCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_OperationInvalidateCallback cb
        cb'' <- mk_OperationInvalidateCallback cb'
        connectSignalFunPtr obj "invalidate" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Vips.Objects.Operation::invalidate"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-vips-8.0.4/docs/GI-Vips-Objects-Operation.html#g:signal:invalidate"})

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Operation
type instance O.AttributeList Operation = OperationAttributeList
type OperationAttributeList = ('[ '("description", Vips.Object.ObjectDescriptionPropertyInfo), '("nickname", Vips.Object.ObjectNicknamePropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Operation = OperationSignalList
type OperationSignalList = ('[ '("close", Vips.Object.ObjectCloseSignalInfo), '("invalidate", OperationInvalidateSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("postbuild", Vips.Object.ObjectPostbuildSignalInfo), '("postclose", Vips.Object.ObjectPostcloseSignalInfo), '("preclose", Vips.Object.ObjectPrecloseSignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method Operation::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "nickname of operation to create"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Vips" , name = "Operation" })
-- throws : False
-- Skip return : False

foreign import ccall "vips_operation_new" vips_operation_new :: 
    CString ->                              -- name : TBasicType TUTF8
    IO (Ptr Operation)

-- | Return a new t'GI.Vips.Objects.Operation.Operation' with the specified nickname. Useful for
-- language bindings.
-- 
-- You\'ll need to set any arguments and build the operation before you can use
-- it. See @/vips_call()/@ for a higher-level way to make new operations.
operationNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@name@/: nickname of operation to create
    -> m Operation
    -- ^ __Returns:__ the new operation.
operationNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m Operation
operationNew Text
name = IO Operation -> m Operation
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Operation -> m Operation) -> IO Operation -> m Operation
forall a b. (a -> b) -> a -> b
$ do
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr Operation
result <- CString -> IO (Ptr Operation)
vips_operation_new CString
name'
    Text -> Ptr Operation -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"operationNew" Ptr Operation
result
    Operation
result' <- ((ManagedPtr Operation -> Operation)
-> Ptr Operation -> IO Operation
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Operation -> Operation
Operation) Ptr Operation
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    Operation -> IO Operation
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Operation
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Operation::get_flags
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "operation"
--           , argType =
--               TInterface Name { namespace = "Vips" , name = "Operation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "operation to fetch flags from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Vips" , name = "OperationFlags" })
-- throws : False
-- Skip return : False

foreign import ccall "vips_operation_get_flags" vips_operation_get_flags :: 
    Ptr Operation ->                        -- operation : TInterface (Name {namespace = "Vips", name = "Operation"})
    IO CUInt

-- | Returns the set of flags for this operation.
operationGetFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsOperation a) =>
    a
    -- ^ /@operation@/: operation to fetch flags from
    -> m [Vips.Flags.OperationFlags]
    -- ^ __Returns:__ 0 on success, or -1 on error.
operationGetFlags :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsOperation a) =>
a -> m [OperationFlags]
operationGetFlags a
operation = IO [OperationFlags] -> m [OperationFlags]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [OperationFlags] -> m [OperationFlags])
-> IO [OperationFlags] -> m [OperationFlags]
forall a b. (a -> b) -> a -> b
$ do
    Ptr Operation
operation' <- a -> IO (Ptr Operation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
operation
    CUInt
result <- Ptr Operation -> IO CUInt
vips_operation_get_flags Ptr Operation
operation'
    let result' :: [OperationFlags]
result' = CUInt -> [OperationFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
operation
    [OperationFlags] -> IO [OperationFlags]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [OperationFlags]
result'

#if defined(ENABLE_OVERLOADING)
data OperationGetFlagsMethodInfo
instance (signature ~ (m [Vips.Flags.OperationFlags]), MonadIO m, IsOperation a) => O.OverloadedMethod OperationGetFlagsMethodInfo a signature where
    overloadedMethod = operationGetFlags

instance O.OverloadedMethodInfo OperationGetFlagsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Vips.Objects.Operation.operationGetFlags",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-vips-8.0.4/docs/GI-Vips-Objects-Operation.html#v:operationGetFlags"
        })


#endif

-- method Operation::invalidate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "operation"
--           , argType =
--               TInterface Name { namespace = "Vips" , name = "Operation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "vips_operation_invalidate" vips_operation_invalidate :: 
    Ptr Operation ->                        -- operation : TInterface (Name {namespace = "Vips", name = "Operation"})
    IO ()

-- | /No description available in the introspection data./
operationInvalidate ::
    (B.CallStack.HasCallStack, MonadIO m, IsOperation a) =>
    a
    -> m ()
operationInvalidate :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsOperation a) =>
a -> m ()
operationInvalidate a
operation = 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 Operation
operation' <- a -> IO (Ptr Operation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
operation
    Ptr Operation -> IO ()
vips_operation_invalidate Ptr Operation
operation'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
operation
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data OperationInvalidateMethodInfo
instance (signature ~ (m ()), MonadIO m, IsOperation a) => O.OverloadedMethod OperationInvalidateMethodInfo a signature where
    overloadedMethod = operationInvalidate

instance O.OverloadedMethodInfo OperationInvalidateMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Vips.Objects.Operation.operationInvalidate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-vips-8.0.4/docs/GI-Vips-Objects-Operation.html#v:operationInvalidate"
        })


#endif

-- method Operation::block_set
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "set block state at this point and below"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "state"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the block state to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "vips_operation_block_set" vips_operation_block_set :: 
    CString ->                              -- name : TBasicType TUTF8
    CInt ->                                 -- state : TBasicType TBoolean
    IO ()

-- | Set the block state on all operations in the libvips class hierarchy at
-- /@name@/ and below.
-- 
-- For example:
-- 
-- >
-- >vips_operation_block_set( "VipsForeignLoad", TRUE );
-- >vips_operation_block_set( "VipsForeignLoadJpeg", FALSE );
-- 
-- 
-- Will block all load operations, except JPEG.
-- 
-- Use @vips -l@ at the command-line to see the class hierarchy.
-- 
-- This call does nothing if the named operation is not found.
-- 
-- See also: 'GI.Vips.Functions.blockUntrustedSet'.
operationBlockSet ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@name@/: set block state at this point and below
    -> Bool
    -- ^ /@state@/: the block state to set
    -> m ()
operationBlockSet :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Bool -> m ()
operationBlockSet Text
name Bool
state = 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
    CString
name' <- Text -> IO CString
textToCString Text
name
    let state' :: CInt
state' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
state
    CString -> CInt -> IO ()
vips_operation_block_set CString
name' CInt
state'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif