{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- 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.JavaScriptCore.Objects.Class
    ( 

-- * Exported types
    Class(..)                               ,
    IsClass                                 ,
    toClass                                 ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addConstructor]("GI.JavaScriptCore.Objects.Class#g:method:addConstructor"), [addConstructorVariadic]("GI.JavaScriptCore.Objects.Class#g:method:addConstructorVariadic"), [addMethod]("GI.JavaScriptCore.Objects.Class#g:method:addMethod"), [addMethodVariadic]("GI.JavaScriptCore.Objects.Class#g:method:addMethodVariadic"), [addProperty]("GI.JavaScriptCore.Objects.Class#g:method:addProperty"), [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"), [getName]("GI.JavaScriptCore.Objects.Class#g:method:getName"), [getParent]("GI.JavaScriptCore.Objects.Class#g:method:getParent"), [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)
    ResolveClassMethod                      ,
#endif

-- ** addConstructor #method:addConstructor#

#if defined(ENABLE_OVERLOADING)
    ClassAddConstructorMethodInfo           ,
#endif
    classAddConstructor                     ,


-- ** addConstructorVariadic #method:addConstructorVariadic#

#if defined(ENABLE_OVERLOADING)
    ClassAddConstructorVariadicMethodInfo   ,
#endif
    classAddConstructorVariadic             ,


-- ** addMethod #method:addMethod#

#if defined(ENABLE_OVERLOADING)
    ClassAddMethodMethodInfo                ,
#endif
    classAddMethod                          ,


-- ** addMethodVariadic #method:addMethodVariadic#

#if defined(ENABLE_OVERLOADING)
    ClassAddMethodVariadicMethodInfo        ,
#endif
    classAddMethodVariadic                  ,


-- ** addProperty #method:addProperty#

#if defined(ENABLE_OVERLOADING)
    ClassAddPropertyMethodInfo              ,
#endif
    classAddProperty                        ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    ClassGetNameMethodInfo                  ,
#endif
    classGetName                            ,


-- ** getParent #method:getParent#

#if defined(ENABLE_OVERLOADING)
    ClassGetParentMethodInfo                ,
#endif
    classGetParent                          ,




 -- * Properties


-- ** context #attr:context#
-- | The t'GI.JavaScriptCore.Objects.Context.Context' in which the class was registered.

#if defined(ENABLE_OVERLOADING)
    ClassContextPropertyInfo                ,
#endif
#if defined(ENABLE_OVERLOADING)
    classContext                            ,
#endif
    constructClassContext                   ,


-- ** name #attr:name#
-- | The name of the class.

#if defined(ENABLE_OVERLOADING)
    ClassNamePropertyInfo                   ,
#endif
#if defined(ENABLE_OVERLOADING)
    className                               ,
#endif
    constructClassName                      ,
    getClassName                            ,


-- ** parent #attr:parent#
-- | The parent class or 'P.Nothing' in case of final classes.

#if defined(ENABLE_OVERLOADING)
    ClassParentPropertyInfo                 ,
#endif
#if defined(ENABLE_OVERLOADING)
    classParent                             ,
#endif
    constructClassParent                    ,
    getClassParent                          ,




    ) 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.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Callbacks as GObject.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.JavaScriptCore.Objects.Context as JavaScriptCore.Context
import {-# SOURCE #-} qualified GI.JavaScriptCore.Objects.Value as JavaScriptCore.Value

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

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

foreign import ccall "jsc_class_get_type"
    c_jsc_class_get_type :: IO B.Types.GType

instance B.Types.TypedObject Class where
    glibType :: IO GType
glibType = IO GType
c_jsc_class_get_type

instance B.Types.GObject Class

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

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

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

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

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

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

#endif

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

#endif

-- VVV Prop "context"
   -- Type: TInterface (Name {namespace = "JavaScriptCore", name = "Context"})
   -- Flags: [PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Construct a `GValueConstruct` with valid value for the “@context@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructClassContext :: (IsClass o, MIO.MonadIO m, JavaScriptCore.Context.IsContext a) => a -> m (GValueConstruct o)
constructClassContext :: forall o (m :: * -> *) a.
(IsClass o, MonadIO m, IsContext a) =>
a -> m (GValueConstruct o)
constructClassContext a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"context" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data ClassContextPropertyInfo
instance AttrInfo ClassContextPropertyInfo where
    type AttrAllowedOps ClassContextPropertyInfo = '[ 'AttrConstruct, 'AttrClear]
    type AttrBaseTypeConstraint ClassContextPropertyInfo = IsClass
    type AttrSetTypeConstraint ClassContextPropertyInfo = JavaScriptCore.Context.IsContext
    type AttrTransferTypeConstraint ClassContextPropertyInfo = JavaScriptCore.Context.IsContext
    type AttrTransferType ClassContextPropertyInfo = JavaScriptCore.Context.Context
    type AttrGetType ClassContextPropertyInfo = ()
    type AttrLabel ClassContextPropertyInfo = "context"
    type AttrOrigin ClassContextPropertyInfo = Class
    attrGet = undefined
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo JavaScriptCore.Context.Context v
    attrConstruct = constructClassContext
    attrClear = undefined
#endif

-- VVV Prop "name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' class #name
-- @
getClassName :: (MonadIO m, IsClass o) => o -> m T.Text
getClassName :: forall (m :: * -> *) o. (MonadIO m, IsClass o) => o -> m Text
getClassName o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getClassName" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"name"

-- | Construct a `GValueConstruct` with valid value for the “@name@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructClassName :: (IsClass o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructClassName :: forall o (m :: * -> *).
(IsClass o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructClassName Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data ClassNamePropertyInfo
instance AttrInfo ClassNamePropertyInfo where
    type AttrAllowedOps ClassNamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ClassNamePropertyInfo = IsClass
    type AttrSetTypeConstraint ClassNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ClassNamePropertyInfo = (~) T.Text
    type AttrTransferType ClassNamePropertyInfo = T.Text
    type AttrGetType ClassNamePropertyInfo = T.Text
    type AttrLabel ClassNamePropertyInfo = "name"
    type AttrOrigin ClassNamePropertyInfo = Class
    attrGet = getClassName
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructClassName
    attrClear = undefined
#endif

-- VVV Prop "parent"
   -- Type: TInterface (Name {namespace = "JavaScriptCore", name = "Class"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@parent@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' class #parent
-- @
getClassParent :: (MonadIO m, IsClass o) => o -> m Class
getClassParent :: forall (m :: * -> *) o. (MonadIO m, IsClass o) => o -> m Class
getClassParent o
obj = IO Class -> m Class
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Class -> m Class) -> IO Class -> m Class
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Class) -> IO Class
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getClassParent" (IO (Maybe Class) -> IO Class) -> IO (Maybe Class) -> IO Class
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Class -> Class) -> IO (Maybe Class)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"parent" ManagedPtr Class -> Class
Class

-- | Construct a `GValueConstruct` with valid value for the “@parent@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructClassParent :: (IsClass o, MIO.MonadIO m, IsClass a) => a -> m (GValueConstruct o)
constructClassParent :: forall o (m :: * -> *) a.
(IsClass o, MonadIO m, IsClass a) =>
a -> m (GValueConstruct o)
constructClassParent a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"parent" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data ClassParentPropertyInfo
instance AttrInfo ClassParentPropertyInfo where
    type AttrAllowedOps ClassParentPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ClassParentPropertyInfo = IsClass
    type AttrSetTypeConstraint ClassParentPropertyInfo = IsClass
    type AttrTransferTypeConstraint ClassParentPropertyInfo = IsClass
    type AttrTransferType ClassParentPropertyInfo = Class
    type AttrGetType ClassParentPropertyInfo = Class
    type AttrLabel ClassParentPropertyInfo = "parent"
    type AttrOrigin ClassParentPropertyInfo = Class
    attrGet = getClassParent
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Class v
    attrConstruct = constructClassParent
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Class
type instance O.AttributeList Class = ClassAttributeList
type ClassAttributeList = ('[ '("context", ClassContextPropertyInfo), '("name", ClassNamePropertyInfo), '("parent", ClassParentPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
classContext :: AttrLabelProxy "context"
classContext = AttrLabelProxy

className :: AttrLabelProxy "name"
className = AttrLabelProxy

classParent :: AttrLabelProxy "parent"
classParent = AttrLabelProxy

#endif

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

#endif

-- method Class::add_constructor_variadic
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "jsc_class"
--           , argType =
--               TInterface Name { namespace = "JavaScriptCore" , name = "Class" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #JSCClass" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the constructor name or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Callback" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #GCallback to be called to create an instance of @jsc_class"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeNotified
--           , argClosure = 3
--           , argDestroy = 4
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data to pass to @callback"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "destroy_notify"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "destroy notifier for @user_data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_type"
--           , argType = TBasicType TGType
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GType of the constructor return value"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "JavaScriptCore" , name = "Value" })
-- throws : False
-- Skip return : False

foreign import ccall "jsc_class_add_constructor_variadic" jsc_class_add_constructor_variadic :: 
    Ptr Class ->                            -- jsc_class : TInterface (Name {namespace = "JavaScriptCore", name = "Class"})
    CString ->                              -- name : TBasicType TUTF8
    FunPtr GObject.Callbacks.C_Callback ->  -- callback : TInterface (Name {namespace = "GObject", name = "Callback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- destroy_notify : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    CGType ->                               -- return_type : TBasicType TGType
    IO (Ptr JavaScriptCore.Value.Value)

-- | Add a constructor to /@jscClass@/. If /@name@/ is 'P.Nothing', the class name will be used. When \<function>new\<\/function>
-- is used with the constructor or @/jsc_value_constructor_call()/@ is called, /@callback@/ is invoked receiving
-- a t'GI.GLib.Structs.PtrArray.PtrArray' of t'GI.JavaScriptCore.Objects.Value.Value's as arguments and /@userData@/ as the last parameter. When the constructor object
-- is cleared in the t'GI.JavaScriptCore.Objects.Class.Class' context, /@destroyNotify@/ is called with /@userData@/ as parameter.
-- 
-- This function creates the constructor, which needs to be added to an object as a property to be able to use it. Use
-- 'GI.JavaScriptCore.Objects.Context.contextSetValue' to make the constructor available in the global object.
-- 
-- Note that the value returned by /@callback@/ is adopted by /@jscClass@/, and the t'GI.GLib.Callbacks.DestroyNotify' passed to
-- 'GI.JavaScriptCore.Objects.Context.contextRegisterClass' is responsible for disposing of it.
classAddConstructorVariadic ::
    (B.CallStack.HasCallStack, MonadIO m, IsClass a) =>
    a
    -- ^ /@jscClass@/: a t'GI.JavaScriptCore.Objects.Class.Class'
    -> Maybe (T.Text)
    -- ^ /@name@/: the constructor name or 'P.Nothing'
    -> GObject.Callbacks.Callback
    -- ^ /@callback@/: a t'GI.GObject.Callbacks.Callback' to be called to create an instance of /@jscClass@/
    -> GType
    -- ^ /@returnType@/: the t'GType' of the constructor return value
    -> m JavaScriptCore.Value.Value
    -- ^ __Returns:__ a t'GI.JavaScriptCore.Objects.Value.Value' representing the class constructor.
classAddConstructorVariadic :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsClass a) =>
a -> Maybe Text -> IO () -> GType -> m Value
classAddConstructorVariadic a
jscClass Maybe Text
name IO ()
callback GType
returnType = IO Value -> m Value
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Value -> m Value) -> IO Value -> m Value
forall a b. (a -> b) -> a -> b
$ do
    Ptr Class
jscClass' <- a -> IO (Ptr Class)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jscClass
    Ptr CChar
maybeName <- case Maybe Text
name of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jName -> do
            Ptr CChar
jName' <- Text -> IO (Ptr CChar)
textToCString Text
jName
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jName'
    FunPtr (IO ())
callback' <- IO () -> IO (FunPtr (IO ()))
GObject.Callbacks.mk_Callback (Maybe (Ptr (FunPtr (IO ()))) -> IO () -> IO ()
GObject.Callbacks.wrap_Callback Maybe (Ptr (FunPtr (IO ())))
forall a. Maybe a
Nothing IO ()
callback)
    let returnType' :: CGType
returnType' = GType -> CGType
gtypeToCGType GType
returnType
    let userData :: Ptr ()
userData = FunPtr (IO ()) -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr (IO ())
callback'
    let destroyNotify :: FunPtr (Ptr a -> IO ())
destroyNotify = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
    Ptr Value
result <- Ptr Class
-> Ptr CChar
-> FunPtr (IO ())
-> Ptr ()
-> FunPtr C_DestroyNotify
-> CGType
-> IO (Ptr Value)
jsc_class_add_constructor_variadic Ptr Class
jscClass' Ptr CChar
maybeName FunPtr (IO ())
callback' Ptr ()
userData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
destroyNotify CGType
returnType'
    Text -> Ptr Value -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"classAddConstructorVariadic" Ptr Value
result
    Value
result' <- ((ManagedPtr Value -> Value) -> Ptr Value -> IO Value
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Value -> Value
JavaScriptCore.Value.Value) Ptr Value
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
jscClass
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeName
    Value -> IO Value
forall (m :: * -> *) a. Monad m => a -> m a
return Value
result'

#if defined(ENABLE_OVERLOADING)
data ClassAddConstructorVariadicMethodInfo
instance (signature ~ (Maybe (T.Text) -> GObject.Callbacks.Callback -> GType -> m JavaScriptCore.Value.Value), MonadIO m, IsClass a) => O.OverloadedMethod ClassAddConstructorVariadicMethodInfo a signature where
    overloadedMethod = classAddConstructorVariadic

instance O.OverloadedMethodInfo ClassAddConstructorVariadicMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.JavaScriptCore.Objects.Class.classAddConstructorVariadic",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-javascriptcore-4.0.23/docs/GI-JavaScriptCore-Objects-Class.html#v:classAddConstructorVariadic"
        }


#endif

-- method Class::add_constructor
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "jsc_class"
--           , argType =
--               TInterface Name { namespace = "JavaScriptCore" , name = "Class" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #JSCClass" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the constructor name or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Callback" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #GCallback to be called to create an instance of @jsc_class"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeNotified
--           , argClosure = 3
--           , argDestroy = 4
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data to pass to @callback"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "destroy_notify"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "destroy notifier for @user_data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_type"
--           , argType = TBasicType TGType
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GType of the constructor return value"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_parameters"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of parameters"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parameter_types"
--           , argType = TCArray False (-1) 6 (TBasicType TGType)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a list of #GType<!-- -->s, one for each parameter, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_parameters"
--              , argType = TBasicType TUInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the number of parameters"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just
--               (TInterface Name { namespace = "JavaScriptCore" , name = "Value" })
-- throws : False
-- Skip return : False

foreign import ccall "jsc_class_add_constructorv" jsc_class_add_constructorv :: 
    Ptr Class ->                            -- jsc_class : TInterface (Name {namespace = "JavaScriptCore", name = "Class"})
    CString ->                              -- name : TBasicType TUTF8
    FunPtr GObject.Callbacks.C_Callback ->  -- callback : TInterface (Name {namespace = "GObject", name = "Callback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- destroy_notify : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    CGType ->                               -- return_type : TBasicType TGType
    Word32 ->                               -- n_parameters : TBasicType TUInt
    Ptr CGType ->                           -- parameter_types : TCArray False (-1) 6 (TBasicType TGType)
    IO (Ptr JavaScriptCore.Value.Value)

-- | Add a constructor to /@jscClass@/. If /@name@/ is 'P.Nothing', the class name will be used. When \<function>new\<\/function>
-- is used with the constructor or @/jsc_value_constructor_call()/@ is called, /@callback@/ is invoked receiving the
-- parameters and /@userData@/ as the last parameter. When the constructor object is cleared in the t'GI.JavaScriptCore.Objects.Class.Class' context,
-- /@destroyNotify@/ is called with /@userData@/ as parameter.
-- 
-- This function creates the constructor, which needs to be added to an object as a property to be able to use it. Use
-- 'GI.JavaScriptCore.Objects.Context.contextSetValue' to make the constructor available in the global object.
-- 
-- Note that the value returned by /@callback@/ is adopted by /@jscClass@/, and the t'GI.GLib.Callbacks.DestroyNotify' passed to
-- 'GI.JavaScriptCore.Objects.Context.contextRegisterClass' is responsible for disposing of it.
classAddConstructor ::
    (B.CallStack.HasCallStack, MonadIO m, IsClass a) =>
    a
    -- ^ /@jscClass@/: a t'GI.JavaScriptCore.Objects.Class.Class'
    -> Maybe (T.Text)
    -- ^ /@name@/: the constructor name or 'P.Nothing'
    -> GObject.Callbacks.Callback
    -- ^ /@callback@/: a t'GI.GObject.Callbacks.Callback' to be called to create an instance of /@jscClass@/
    -> GType
    -- ^ /@returnType@/: the t'GType' of the constructor return value
    -> Maybe ([GType])
    -- ^ /@parameterTypes@/: a list of t'GType's, one for each parameter, or 'P.Nothing'
    -> m JavaScriptCore.Value.Value
    -- ^ __Returns:__ a t'GI.JavaScriptCore.Objects.Value.Value' representing the class constructor.
classAddConstructor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsClass a) =>
a -> Maybe Text -> IO () -> GType -> Maybe [GType] -> m Value
classAddConstructor a
jscClass Maybe Text
name IO ()
callback GType
returnType Maybe [GType]
parameterTypes = IO Value -> m Value
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Value -> m Value) -> IO Value -> m Value
forall a b. (a -> b) -> a -> b
$ do
    let nParameters :: Word32
nParameters = case Maybe [GType]
parameterTypes of
            Maybe [GType]
Nothing -> Word32
0
            Just [GType]
jParameterTypes -> Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ [GType] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [GType]
jParameterTypes
    Ptr Class
jscClass' <- a -> IO (Ptr Class)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jscClass
    Ptr CChar
maybeName <- case Maybe Text
name of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jName -> do
            Ptr CChar
jName' <- Text -> IO (Ptr CChar)
textToCString Text
jName
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jName'
    FunPtr (IO ())
callback' <- IO () -> IO (FunPtr (IO ()))
GObject.Callbacks.mk_Callback (Maybe (Ptr (FunPtr (IO ()))) -> IO () -> IO ()
GObject.Callbacks.wrap_Callback Maybe (Ptr (FunPtr (IO ())))
forall a. Maybe a
Nothing IO ()
callback)
    let returnType' :: CGType
returnType' = GType -> CGType
gtypeToCGType GType
returnType
    Ptr CGType
maybeParameterTypes <- case Maybe [GType]
parameterTypes of
        Maybe [GType]
Nothing -> Ptr CGType -> IO (Ptr CGType)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CGType
forall a. Ptr a
nullPtr
        Just [GType]
jParameterTypes -> do
            Ptr CGType
jParameterTypes' <- ((GType -> CGType) -> [GType] -> IO (Ptr CGType)
forall a b. Storable b => (a -> b) -> [a] -> IO (Ptr b)
packMapStorableArray GType -> CGType
gtypeToCGType) [GType]
jParameterTypes
            Ptr CGType -> IO (Ptr CGType)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CGType
jParameterTypes'
    let userData :: Ptr ()
userData = FunPtr (IO ()) -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr (IO ())
callback'
    let destroyNotify :: FunPtr (Ptr a -> IO ())
destroyNotify = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
    Ptr Value
result <- Ptr Class
-> Ptr CChar
-> FunPtr (IO ())
-> Ptr ()
-> FunPtr C_DestroyNotify
-> CGType
-> Word32
-> Ptr CGType
-> IO (Ptr Value)
jsc_class_add_constructorv Ptr Class
jscClass' Ptr CChar
maybeName FunPtr (IO ())
callback' Ptr ()
userData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
destroyNotify CGType
returnType' Word32
nParameters Ptr CGType
maybeParameterTypes
    Text -> Ptr Value -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"classAddConstructor" Ptr Value
result
    Value
result' <- ((ManagedPtr Value -> Value) -> Ptr Value -> IO Value
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Value -> Value
JavaScriptCore.Value.Value) Ptr Value
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
jscClass
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeName
    Ptr CGType -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CGType
maybeParameterTypes
    Value -> IO Value
forall (m :: * -> *) a. Monad m => a -> m a
return Value
result'

#if defined(ENABLE_OVERLOADING)
data ClassAddConstructorMethodInfo
instance (signature ~ (Maybe (T.Text) -> GObject.Callbacks.Callback -> GType -> Maybe ([GType]) -> m JavaScriptCore.Value.Value), MonadIO m, IsClass a) => O.OverloadedMethod ClassAddConstructorMethodInfo a signature where
    overloadedMethod = classAddConstructor

instance O.OverloadedMethodInfo ClassAddConstructorMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.JavaScriptCore.Objects.Class.classAddConstructor",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-javascriptcore-4.0.23/docs/GI-JavaScriptCore-Objects-Class.html#v:classAddConstructor"
        }


#endif

-- method Class::add_method_variadic
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "jsc_class"
--           , argType =
--               TInterface Name { namespace = "JavaScriptCore" , name = "Class" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #JSCClass" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the method name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Callback" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #GCallback to be called to invoke method @name of @jsc_class"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeNotified
--           , argClosure = 3
--           , argDestroy = 4
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data to pass to @callback"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "destroy_notify"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "destroy notifier for @user_data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_type"
--           , argType = TBasicType TGType
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the #GType of the method return value, or %G_TYPE_NONE if the method is void."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "jsc_class_add_method_variadic" jsc_class_add_method_variadic :: 
    Ptr Class ->                            -- jsc_class : TInterface (Name {namespace = "JavaScriptCore", name = "Class"})
    CString ->                              -- name : TBasicType TUTF8
    FunPtr GObject.Callbacks.C_Callback ->  -- callback : TInterface (Name {namespace = "GObject", name = "Callback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- destroy_notify : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    CGType ->                               -- return_type : TBasicType TGType
    IO ()

-- | Add method with /@name@/ to /@jscClass@/. When the method is called by JavaScript or @/jsc_value_object_invoke_method()/@,
-- /@callback@/ is called receiving the class instance as first parameter, followed by a t'GI.GLib.Structs.PtrArray.PtrArray' of t'GI.JavaScriptCore.Objects.Value.Value's
-- with the method arguments and then /@userData@/ as last parameter. When the method is cleared in the t'GI.JavaScriptCore.Objects.Class.Class' context,
-- /@destroyNotify@/ is called with /@userData@/ as parameter.
-- 
-- Note that the value returned by /@callback@/ must be transfer full. In case of non-refcounted boxed types, you should use
-- @/G_TYPE_POINTER/@ instead of the actual boxed t'GType' to ensure that the instance owned by t'GI.JavaScriptCore.Objects.Class.Class' is used.
-- If you really want to return a new copy of the boxed type, use @/JSC_TYPE_VALUE/@ and return a t'GI.JavaScriptCore.Objects.Value.Value' created
-- with 'GI.JavaScriptCore.Objects.Value.valueNewObject' that receives the copy as the instance parameter.
classAddMethodVariadic ::
    (B.CallStack.HasCallStack, MonadIO m, IsClass a) =>
    a
    -- ^ /@jscClass@/: a t'GI.JavaScriptCore.Objects.Class.Class'
    -> T.Text
    -- ^ /@name@/: the method name
    -> GObject.Callbacks.Callback
    -- ^ /@callback@/: a t'GI.GObject.Callbacks.Callback' to be called to invoke method /@name@/ of /@jscClass@/
    -> GType
    -- ^ /@returnType@/: the t'GType' of the method return value, or @/G_TYPE_NONE/@ if the method is void.
    -> m ()
classAddMethodVariadic :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsClass a) =>
a -> Text -> IO () -> GType -> m ()
classAddMethodVariadic a
jscClass Text
name IO ()
callback GType
returnType = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Class
jscClass' <- a -> IO (Ptr Class)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jscClass
    Ptr CChar
name' <- Text -> IO (Ptr CChar)
textToCString Text
name
    FunPtr (IO ())
callback' <- IO () -> IO (FunPtr (IO ()))
GObject.Callbacks.mk_Callback (Maybe (Ptr (FunPtr (IO ()))) -> IO () -> IO ()
GObject.Callbacks.wrap_Callback Maybe (Ptr (FunPtr (IO ())))
forall a. Maybe a
Nothing IO ()
callback)
    let returnType' :: CGType
returnType' = GType -> CGType
gtypeToCGType GType
returnType
    let userData :: Ptr ()
userData = FunPtr (IO ()) -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr (IO ())
callback'
    let destroyNotify :: FunPtr (Ptr a -> IO ())
destroyNotify = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
    Ptr Class
-> Ptr CChar
-> FunPtr (IO ())
-> Ptr ()
-> FunPtr C_DestroyNotify
-> CGType
-> IO ()
jsc_class_add_method_variadic Ptr Class
jscClass' Ptr CChar
name' FunPtr (IO ())
callback' Ptr ()
userData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
destroyNotify CGType
returnType'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
jscClass
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
name'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ClassAddMethodVariadicMethodInfo
instance (signature ~ (T.Text -> GObject.Callbacks.Callback -> GType -> m ()), MonadIO m, IsClass a) => O.OverloadedMethod ClassAddMethodVariadicMethodInfo a signature where
    overloadedMethod = classAddMethodVariadic

instance O.OverloadedMethodInfo ClassAddMethodVariadicMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.JavaScriptCore.Objects.Class.classAddMethodVariadic",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-javascriptcore-4.0.23/docs/GI-JavaScriptCore-Objects-Class.html#v:classAddMethodVariadic"
        }


#endif

-- method Class::add_method
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "jsc_class"
--           , argType =
--               TInterface Name { namespace = "JavaScriptCore" , name = "Class" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #JSCClass" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the method name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Callback" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #GCallback to be called to invoke method @name of @jsc_class"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeNotified
--           , argClosure = 3
--           , argDestroy = 4
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data to pass to @callback"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "destroy_notify"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "destroy notifier for @user_data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_type"
--           , argType = TBasicType TGType
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the #GType of the method return value, or %G_TYPE_NONE if the method is void."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_parameters"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the number of parameter types to follow or 0 if the method doesn't receive parameters."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parameter_types"
--           , argType = TCArray False (-1) 6 (TBasicType TGType)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a list of #GType<!-- -->s, one for each parameter, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_parameters"
--              , argType = TBasicType TUInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just
--                          "the number of parameter types to follow or 0 if the method doesn't receive parameters."
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "jsc_class_add_methodv" jsc_class_add_methodv :: 
    Ptr Class ->                            -- jsc_class : TInterface (Name {namespace = "JavaScriptCore", name = "Class"})
    CString ->                              -- name : TBasicType TUTF8
    FunPtr GObject.Callbacks.C_Callback ->  -- callback : TInterface (Name {namespace = "GObject", name = "Callback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- destroy_notify : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    CGType ->                               -- return_type : TBasicType TGType
    Word32 ->                               -- n_parameters : TBasicType TUInt
    Ptr CGType ->                           -- parameter_types : TCArray False (-1) 6 (TBasicType TGType)
    IO ()

-- | Add method with /@name@/ to /@jscClass@/. When the method is called by JavaScript or @/jsc_value_object_invoke_method()/@,
-- /@callback@/ is called receiving the class instance as first parameter, followed by the method parameters and then
-- /@userData@/ as last parameter. When the method is cleared in the t'GI.JavaScriptCore.Objects.Class.Class' context, /@destroyNotify@/ is called with
-- /@userData@/ as parameter.
-- 
-- Note that the value returned by /@callback@/ must be transfer full. In case of non-refcounted boxed types, you should use
-- @/G_TYPE_POINTER/@ instead of the actual boxed t'GType' to ensure that the instance owned by t'GI.JavaScriptCore.Objects.Class.Class' is used.
-- If you really want to return a new copy of the boxed type, use @/JSC_TYPE_VALUE/@ and return a t'GI.JavaScriptCore.Objects.Value.Value' created
-- with 'GI.JavaScriptCore.Objects.Value.valueNewObject' that receives the copy as the instance parameter.
classAddMethod ::
    (B.CallStack.HasCallStack, MonadIO m, IsClass a) =>
    a
    -- ^ /@jscClass@/: a t'GI.JavaScriptCore.Objects.Class.Class'
    -> T.Text
    -- ^ /@name@/: the method name
    -> GObject.Callbacks.Callback
    -- ^ /@callback@/: a t'GI.GObject.Callbacks.Callback' to be called to invoke method /@name@/ of /@jscClass@/
    -> GType
    -- ^ /@returnType@/: the t'GType' of the method return value, or @/G_TYPE_NONE/@ if the method is void.
    -> Maybe ([GType])
    -- ^ /@parameterTypes@/: a list of t'GType's, one for each parameter, or 'P.Nothing'
    -> m ()
classAddMethod :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsClass a) =>
a -> Text -> IO () -> GType -> Maybe [GType] -> m ()
classAddMethod a
jscClass Text
name IO ()
callback GType
returnType Maybe [GType]
parameterTypes = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    let nParameters :: Word32
nParameters = case Maybe [GType]
parameterTypes of
            Maybe [GType]
Nothing -> Word32
0
            Just [GType]
jParameterTypes -> Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ [GType] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [GType]
jParameterTypes
    Ptr Class
jscClass' <- a -> IO (Ptr Class)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jscClass
    Ptr CChar
name' <- Text -> IO (Ptr CChar)
textToCString Text
name
    FunPtr (IO ())
callback' <- IO () -> IO (FunPtr (IO ()))
GObject.Callbacks.mk_Callback (Maybe (Ptr (FunPtr (IO ()))) -> IO () -> IO ()
GObject.Callbacks.wrap_Callback Maybe (Ptr (FunPtr (IO ())))
forall a. Maybe a
Nothing IO ()
callback)
    let returnType' :: CGType
returnType' = GType -> CGType
gtypeToCGType GType
returnType
    Ptr CGType
maybeParameterTypes <- case Maybe [GType]
parameterTypes of
        Maybe [GType]
Nothing -> Ptr CGType -> IO (Ptr CGType)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CGType
forall a. Ptr a
nullPtr
        Just [GType]
jParameterTypes -> do
            Ptr CGType
jParameterTypes' <- ((GType -> CGType) -> [GType] -> IO (Ptr CGType)
forall a b. Storable b => (a -> b) -> [a] -> IO (Ptr b)
packMapStorableArray GType -> CGType
gtypeToCGType) [GType]
jParameterTypes
            Ptr CGType -> IO (Ptr CGType)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CGType
jParameterTypes'
    let userData :: Ptr ()
userData = FunPtr (IO ()) -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr (IO ())
callback'
    let destroyNotify :: FunPtr (Ptr a -> IO ())
destroyNotify = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
    Ptr Class
-> Ptr CChar
-> FunPtr (IO ())
-> Ptr ()
-> FunPtr C_DestroyNotify
-> CGType
-> Word32
-> Ptr CGType
-> IO ()
jsc_class_add_methodv Ptr Class
jscClass' Ptr CChar
name' FunPtr (IO ())
callback' Ptr ()
userData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
destroyNotify CGType
returnType' Word32
nParameters Ptr CGType
maybeParameterTypes
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
jscClass
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
name'
    Ptr CGType -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CGType
maybeParameterTypes
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ClassAddMethodMethodInfo
instance (signature ~ (T.Text -> GObject.Callbacks.Callback -> GType -> Maybe ([GType]) -> m ()), MonadIO m, IsClass a) => O.OverloadedMethod ClassAddMethodMethodInfo a signature where
    overloadedMethod = classAddMethod

instance O.OverloadedMethodInfo ClassAddMethodMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.JavaScriptCore.Objects.Class.classAddMethod",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-javascriptcore-4.0.23/docs/GI-JavaScriptCore-Objects-Class.html#v:classAddMethod"
        }


#endif

-- method Class::add_property
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "jsc_class"
--           , argType =
--               TInterface Name { namespace = "JavaScriptCore" , name = "Class" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #JSCClass" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the property name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property_type"
--           , argType = TBasicType TGType
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GType of the property value"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "getter"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Callback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GCallback to be called to get the property value"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "setter"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Callback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GCallback to be called to set the property value"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeNotified
--           , argClosure = 5
--           , argDestroy = 6
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data to pass to @getter and @setter"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "destroy_notify"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "destroy notifier for @user_data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "jsc_class_add_property" jsc_class_add_property :: 
    Ptr Class ->                            -- jsc_class : TInterface (Name {namespace = "JavaScriptCore", name = "Class"})
    CString ->                              -- name : TBasicType TUTF8
    CGType ->                               -- property_type : TBasicType TGType
    FunPtr GObject.Callbacks.C_Callback ->  -- getter : TInterface (Name {namespace = "GObject", name = "Callback"})
    FunPtr GObject.Callbacks.C_Callback ->  -- setter : TInterface (Name {namespace = "GObject", name = "Callback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- destroy_notify : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO ()

-- | Add a property with /@name@/ to /@jscClass@/. When the property value needs to be getted, /@getter@/ is called
-- receiving the the class instance as first parameter and /@userData@/ as last parameter. When the property
-- value needs to be set, /@setter@/ is called receiving the the class instance as first parameter, followed
-- by the value to be set and then /@userData@/ as the last parameter. When the property is cleared in the
-- t'GI.JavaScriptCore.Objects.Class.Class' context, /@destroyNotify@/ is called with /@userData@/ as parameter.
-- 
-- Note that the value returned by /@getter@/ must be transfer full. In case of non-refcounted boxed types, you should use
-- @/G_TYPE_POINTER/@ instead of the actual boxed t'GType' to ensure that the instance owned by t'GI.JavaScriptCore.Objects.Class.Class' is used.
-- If you really want to return a new copy of the boxed type, use @/JSC_TYPE_VALUE/@ and return a t'GI.JavaScriptCore.Objects.Value.Value' created
-- with 'GI.JavaScriptCore.Objects.Value.valueNewObject' that receives the copy as the instance parameter.
classAddProperty ::
    (B.CallStack.HasCallStack, MonadIO m, IsClass a) =>
    a
    -- ^ /@jscClass@/: a t'GI.JavaScriptCore.Objects.Class.Class'
    -> T.Text
    -- ^ /@name@/: the property name
    -> GType
    -- ^ /@propertyType@/: the t'GType' of the property value
    -> Maybe (GObject.Callbacks.Callback)
    -- ^ /@getter@/: a t'GI.GObject.Callbacks.Callback' to be called to get the property value
    -> Maybe (GObject.Callbacks.Callback)
    -- ^ /@setter@/: a t'GI.GObject.Callbacks.Callback' to be called to set the property value
    -> m ()
classAddProperty :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsClass a) =>
a -> Text -> GType -> Maybe (IO ()) -> Maybe (IO ()) -> m ()
classAddProperty a
jscClass Text
name GType
propertyType Maybe (IO ())
getter Maybe (IO ())
setter = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Class
jscClass' <- a -> IO (Ptr Class)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jscClass
    Ptr CChar
name' <- Text -> IO (Ptr CChar)
textToCString Text
name
    let propertyType' :: CGType
propertyType' = GType -> CGType
gtypeToCGType GType
propertyType
    FunPtr (IO ())
maybeGetter <- case Maybe (IO ())
getter of
        Maybe (IO ())
Nothing -> FunPtr (IO ()) -> IO (FunPtr (IO ()))
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr (IO ())
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just IO ()
jGetter -> do
            Ptr (FunPtr (IO ()))
ptrgetter <- IO (Ptr (FunPtr (IO ())))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr GObject.Callbacks.C_Callback))
            FunPtr (IO ())
jGetter' <- IO () -> IO (FunPtr (IO ()))
GObject.Callbacks.mk_Callback (Maybe (Ptr (FunPtr (IO ()))) -> IO () -> IO ()
GObject.Callbacks.wrap_Callback (Ptr (FunPtr (IO ())) -> Maybe (Ptr (FunPtr (IO ())))
forall a. a -> Maybe a
Just Ptr (FunPtr (IO ()))
ptrgetter) IO ()
jGetter)
            Ptr (FunPtr (IO ())) -> FunPtr (IO ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr (IO ()))
ptrgetter FunPtr (IO ())
jGetter'
            FunPtr (IO ()) -> IO (FunPtr (IO ()))
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr (IO ())
jGetter'
    FunPtr (IO ())
maybeSetter <- case Maybe (IO ())
setter of
        Maybe (IO ())
Nothing -> FunPtr (IO ()) -> IO (FunPtr (IO ()))
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr (IO ())
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just IO ()
jSetter -> do
            FunPtr (IO ())
jSetter' <- IO () -> IO (FunPtr (IO ()))
GObject.Callbacks.mk_Callback (Maybe (Ptr (FunPtr (IO ()))) -> IO () -> IO ()
GObject.Callbacks.wrap_Callback Maybe (Ptr (FunPtr (IO ())))
forall a. Maybe a
Nothing IO ()
jSetter)
            FunPtr (IO ()) -> IO (FunPtr (IO ()))
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr (IO ())
jSetter'
    let userData :: Ptr ()
userData = FunPtr (IO ()) -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr (IO ())
maybeSetter
    let destroyNotify :: FunPtr (Ptr a -> IO ())
destroyNotify = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
    Ptr Class
-> Ptr CChar
-> CGType
-> FunPtr (IO ())
-> FunPtr (IO ())
-> Ptr ()
-> FunPtr C_DestroyNotify
-> IO ()
jsc_class_add_property Ptr Class
jscClass' Ptr CChar
name' CGType
propertyType' FunPtr (IO ())
maybeGetter FunPtr (IO ())
maybeSetter Ptr ()
userData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
destroyNotify
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
jscClass
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
name'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ClassAddPropertyMethodInfo
instance (signature ~ (T.Text -> GType -> Maybe (GObject.Callbacks.Callback) -> Maybe (GObject.Callbacks.Callback) -> m ()), MonadIO m, IsClass a) => O.OverloadedMethod ClassAddPropertyMethodInfo a signature where
    overloadedMethod = classAddProperty

instance O.OverloadedMethodInfo ClassAddPropertyMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.JavaScriptCore.Objects.Class.classAddProperty",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-javascriptcore-4.0.23/docs/GI-JavaScriptCore-Objects-Class.html#v:classAddProperty"
        }


#endif

-- method Class::get_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "jsc_class"
--           , argType =
--               TInterface Name { namespace = "JavaScriptCore" , name = "Class" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a @JSCClass" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "jsc_class_get_name" jsc_class_get_name :: 
    Ptr Class ->                            -- jsc_class : TInterface (Name {namespace = "JavaScriptCore", name = "Class"})
    IO CString

-- | Get the class name of /@jscClass@/
classGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsClass a) =>
    a
    -- ^ /@jscClass@/: a /@jSCClass@/
    -> m T.Text
    -- ^ __Returns:__ the name of /@jscClass@/
classGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsClass a) =>
a -> m Text
classGetName a
jscClass = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr Class
jscClass' <- a -> IO (Ptr Class)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jscClass
    Ptr CChar
result <- Ptr Class -> IO (Ptr CChar)
jsc_class_get_name Ptr Class
jscClass'
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"classGetName" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
jscClass
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ClassGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsClass a) => O.OverloadedMethod ClassGetNameMethodInfo a signature where
    overloadedMethod = classGetName

instance O.OverloadedMethodInfo ClassGetNameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.JavaScriptCore.Objects.Class.classGetName",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-javascriptcore-4.0.23/docs/GI-JavaScriptCore-Objects-Class.html#v:classGetName"
        }


#endif

-- method Class::get_parent
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "jsc_class"
--           , argType =
--               TInterface Name { namespace = "JavaScriptCore" , name = "Class" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a @JSCClass" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "JavaScriptCore" , name = "Class" })
-- throws : False
-- Skip return : False

foreign import ccall "jsc_class_get_parent" jsc_class_get_parent :: 
    Ptr Class ->                            -- jsc_class : TInterface (Name {namespace = "JavaScriptCore", name = "Class"})
    IO (Ptr Class)

-- | Get the parent class of /@jscClass@/
classGetParent ::
    (B.CallStack.HasCallStack, MonadIO m, IsClass a) =>
    a
    -- ^ /@jscClass@/: a /@jSCClass@/
    -> m Class
    -- ^ __Returns:__ the parent class of /@jscClass@/
classGetParent :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsClass a) =>
a -> m Class
classGetParent a
jscClass = IO Class -> m Class
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Class -> m Class) -> IO Class -> m Class
forall a b. (a -> b) -> a -> b
$ do
    Ptr Class
jscClass' <- a -> IO (Ptr Class)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jscClass
    Ptr Class
result <- Ptr Class -> IO (Ptr Class)
jsc_class_get_parent Ptr Class
jscClass'
    Text -> Ptr Class -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"classGetParent" Ptr Class
result
    Class
result' <- ((ManagedPtr Class -> Class) -> Ptr Class -> IO Class
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Class -> Class
Class) Ptr Class
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
jscClass
    Class -> IO Class
forall (m :: * -> *) a. Monad m => a -> m a
return Class
result'

#if defined(ENABLE_OVERLOADING)
data ClassGetParentMethodInfo
instance (signature ~ (m Class), MonadIO m, IsClass a) => O.OverloadedMethod ClassGetParentMethodInfo a signature where
    overloadedMethod = classGetParent

instance O.OverloadedMethodInfo ClassGetParentMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.JavaScriptCore.Objects.Class.classGetParent",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-javascriptcore-4.0.23/docs/GI-JavaScriptCore-Objects-Class.html#v:classGetParent"
        }


#endif